From 6a235ba60693596af3f13b093b83defa37501e09 Mon Sep 17 00:00:00 2001
From: Alexander Kondratskiy
Date: Sat, 13 Jul 2013 02:23:27 -0400
Subject: Checking options before applying syntax highlighting for HTML output
---
src/Text/Pandoc/Writers/HTML.hs | 12 +++++++++---
1 file changed, 9 insertions(+), 3 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 57bf2a349..cfc187e02 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -422,7 +422,10 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
adjCode = if tolhs
then unlines . map ("> " ++) . lines $ rawCode
else rawCode
- case highlight formatHtmlBlock (id',classes',keyvals) adjCode of
+ hlCode = if writerHighlight opts -- check highlighting options
+ then highlight formatHtmlBlock (id',classes',keyvals) adjCode
+ else Nothing
+ case hlCode of
Nothing -> return $ addAttrs opts (id',classes,keyvals)
$ H.pre $ H.code $ toHtml adjCode
Just h -> modify (\st -> st{ stHighlighting = True }) >>
@@ -589,14 +592,17 @@ inlineToHtml opts inline =
(LineBreak) -> return $ if writerHtml5 opts then H5.br else H.br
(Emph lst) -> inlineListToHtml opts lst >>= return . H.em
(Strong lst) -> inlineListToHtml opts lst >>= return . H.strong
- (Code attr str) -> case highlight formatHtmlInline attr str of
+ (Code attr str) -> case hlCode of
Nothing -> return
$ addAttrs opts attr
$ H.code $ strToHtml str
Just h -> do
modify $ \st -> st{ stHighlighting = True }
return $ addAttrs opts (id',[],keyvals) h
- where (id',_,keyvals) = attr
+ where (id',_,keyvals) = attr
+ hlCode = if writerHighlight opts
+ then highlight formatHtmlInline attr str
+ else Nothing
(Strikeout lst) -> inlineListToHtml opts lst >>=
return . H.del
(SmallCaps lst) -> inlineListToHtml opts lst >>=
--
cgit v1.2.3
From f42095b7b72fc3419a661c65d17f46ba3cbc8d62 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sat, 13 Jul 2013 13:48:50 -0700
Subject: Docx writer: Make `--no-highlight` work properly.
---
src/Text/Pandoc/Writers/Docx.hs | 18 +++++++++++-------
1 file changed, 11 insertions(+), 7 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index e899200f6..d579d4fa6 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -214,7 +214,8 @@ writeDocx opts doc@(Pandoc meta _) = do
let newstyles = styleToOpenXml $ writerHighlightStyle opts
let stylepath = "word/styles.xml"
styledoc <- parseXml refArchive stylepath
- let styledoc' = styledoc{ elContent = elContent styledoc ++ map Elem newstyles }
+ let styledoc' = styledoc{ elContent = elContent styledoc ++
+ [Elem x | x <- newstyles, writerHighlight opts] }
let styleEntry = toEntry stylepath epochtime $ renderXml styledoc'
-- construct word/numbering.xml
@@ -665,13 +666,16 @@ inlineToOpenXML opts (Math mathType str) = do
Right r -> return [r]
Left _ -> inlinesToOpenXML opts (readTeXMath str)
inlineToOpenXML opts (Cite _ lst) = inlinesToOpenXML opts lst
-inlineToOpenXML _ (Code attrs str) =
+inlineToOpenXML opts (Code attrs str) =
withTextProp (rStyle "VerbatimChar")
- $ case highlight formatOpenXML attrs str of
- Nothing -> intercalate [br]
- `fmap` (mapM formattedString $ lines str)
- Just h -> return h
- where formatOpenXML _fmtOpts = intercalate [br] . map (map toHlTok)
+ $ if writerHighlight opts
+ then case highlight formatOpenXML attrs str of
+ Nothing -> unhighlighted
+ Just h -> return h
+ else unhighlighted
+ where unhighlighted = intercalate [br] `fmap`
+ (mapM formattedString $ lines str)
+ formatOpenXML _fmtOpts = intercalate [br] . map (map toHlTok)
toHlTok (toktype,tok) = mknode "w:r" []
[ mknode "w:rPr" []
[ rStyle $ show toktype ]
--
cgit v1.2.3
From 0b49f810f401b9154b50727d2179d1ec39cd8d3e Mon Sep 17 00:00:00 2001
From: Alexander Kondratskiy
Date: Sun, 14 Jul 2013 14:33:58 -0400
Subject: Fixing wrong numbered-list indentation in open document format
---
src/Text/Pandoc/Writers/OpenDocument.hs | 12 ++++++-----
tests/writer.opendocument | 38 ++++++++++++++++-----------------
2 files changed, 26 insertions(+), 24 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 30f99c3e4..0efbf7580 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -489,14 +489,16 @@ paraStyle parent attrs = do
tight = if t then [ ("fo:margin-top" , "0in" )
, ("fo:margin-bottom" , "0in" )]
else []
- indent = when (i /= 0 || b || t) $
- selfClosingTag "style:paragraph-properties" $
- [ ("fo:margin-left" , indentVal)
+ indent = if (i /= 0 || b)
+ then [ ("fo:margin-left" , indentVal)
, ("fo:margin-right" , "0in" )
, ("fo:text-indent" , "0in" )
, ("style:auto-text-indent" , "false" )]
- ++ tight
- addParaStyle $ inTags True "style:style" (styleAttr ++ attrs) indent
+ else []
+ attributes = indent ++ tight
+ paraProps = when (not $ null attributes) $
+ selfClosingTag "style:paragraph-properties" attributes
+ addParaStyle $ inTags True "style:style" (styleAttr ++ attrs) paraProps
return pn
paraListStyle :: Int -> State WriterState Int
diff --git a/tests/writer.opendocument b/tests/writer.opendocument
index 8727373a0..9e1661475 100644
--- a/tests/writer.opendocument
+++ b/tests/writer.opendocument
@@ -741,25 +741,25 @@
-
+
-
+
-
+
-
+
-
+
@@ -768,37 +768,37 @@
-
+
-
+
-
+
-
+
-
+
-
+
-
+
-
+
-
+
@@ -822,18 +822,18 @@
-
+
-
+
-
+
-
+
@@ -846,7 +846,7 @@
-
+
--
cgit v1.2.3
From b2385d0e9bf13f2fc152a3983893c47f2ab5d4c0 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Tue, 16 Jul 2013 22:04:59 -0700
Subject: Text.Pandoc.ImageSize: Handle EPS.
Closes #903. This change will make EPS images properly sized
on conversion to Word.
---
src/Text/Pandoc/ImageSize.hs | 24 +++++++++++++++++++++++-
src/Text/Pandoc/Writers/Docx.hs | 1 +
2 files changed, 24 insertions(+), 1 deletion(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs
index 273a1a428..9b0850efb 100644
--- a/src/Text/Pandoc/ImageSize.hs
+++ b/src/Text/Pandoc/ImageSize.hs
@@ -34,11 +34,12 @@ import Data.ByteString (ByteString, unpack)
import qualified Data.ByteString.Char8 as B
import Control.Monad
import Data.Bits
+import Text.Pandoc.Shared (safeRead)
-- quick and dirty functions to get image sizes
-- algorithms borrowed from wwwis.pl
-data ImageType = Png | Gif | Jpeg | Pdf deriving Show
+data ImageType = Png | Gif | Jpeg | Pdf | Eps deriving Show
data ImageSize = ImageSize{
pxX :: Integer
@@ -54,6 +55,9 @@ imageType img = case B.take 4 img of
"\x47\x49\x46\x38" -> return Gif
"\xff\xd8\xff\xe0" -> return Jpeg
"%PDF" -> return Pdf
+ "%!PS"
+ | (B.take 4 $ B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF"
+ -> return Eps
_ -> fail "Unknown image type"
imageSize :: ByteString -> Maybe ImageSize
@@ -63,6 +67,7 @@ imageSize img = do
Png -> pngSize img
Gif -> gifSize img
Jpeg -> jpegSize img
+ Eps -> epsSize img
Pdf -> Nothing -- TODO
sizeInPixels :: ImageSize -> (Integer, Integer)
@@ -71,6 +76,23 @@ sizeInPixels s = (pxX s, pxY s)
sizeInPoints :: ImageSize -> (Integer, Integer)
sizeInPoints s = (pxX s * 72 `div` dpiX s, pxY s * 72 `div` dpiY s)
+epsSize :: ByteString -> Maybe ImageSize
+epsSize img = do
+ let ls = takeWhile ("%" `B.isPrefixOf`) $ B.lines img
+ let ls' = dropWhile (not . ("%%BoundingBox:" `B.isPrefixOf`)) ls
+ case ls' of
+ [] -> mzero
+ (x:_) -> case B.words x of
+ (_:_:_:ux:uy:[]) -> do
+ ux' <- safeRead $ B.unpack ux
+ uy' <- safeRead $ B.unpack uy
+ return ImageSize{
+ pxX = ux'
+ , pxY = uy'
+ , dpiX = 72
+ , dpiY = 72 }
+ _ -> mzero
+
pngSize :: ByteString -> Maybe ImageSize
pngSize img = do
let (h, rest) = B.splitAt 8 img
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index d579d4fa6..1ed8c2fa5 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -776,6 +776,7 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
Just Jpeg -> ".jpeg"
Just Gif -> ".gif"
Just Pdf -> ".pdf"
+ Just Eps -> ".eps"
Nothing -> takeExtension src
if null imgext
then -- without an extension there is no rule for content type
--
cgit v1.2.3
From 7c980f39bf1cff941d3e78056fd69e0b371833e3 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 18 Jul 2013 20:58:14 -0700
Subject: Improved fetching of external resources.
* In Shared, openURL and fetchItem now return an Either, for
better error handling. (API change.)
* Better error message when fetching a URL fails with
`--self-contained`.
* EPUB writer: If resource not found, skip it, as in Docx writer.
* Closes #916.
---
src/Text/Pandoc/SelfContained.hs | 5 +++--
src/Text/Pandoc/Shared.hs | 16 +++++++++-------
src/Text/Pandoc/Writers/Docx.hs | 2 +-
src/Text/Pandoc/Writers/EPUB.hs | 13 +++++++++----
src/Text/Pandoc/Writers/ODT.hs | 5 ++---
5 files changed, 24 insertions(+), 17 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs
index c4613992a..0547bc065 100644
--- a/src/Text/Pandoc/SelfContained.hs
+++ b/src/Text/Pandoc/SelfContained.hs
@@ -40,7 +40,7 @@ import System.FilePath (takeExtension, dropExtension, takeDirectory, (>))
import Data.Char (toLower, isAscii, isAlphaNum)
import Codec.Compression.GZip as Gzip
import qualified Data.ByteString.Lazy as L
-import Text.Pandoc.Shared (renderTags', openURL, readDataFile)
+import Text.Pandoc.Shared (renderTags', openURL, readDataFile, err)
import Text.Pandoc.UTF8 (toString, fromString)
import Text.Pandoc.MIME (getMimeType)
import System.Directory (doesFileExist)
@@ -98,7 +98,7 @@ cssURLs userdata d orig =
getItem :: Maybe FilePath -> String -> IO (ByteString, Maybe String)
getItem userdata f =
if isAbsoluteURI f
- then openURL f
+ then openURL f >>= either handleErr return
else do
-- strip off trailing query or fragment part, if relative URL.
-- this is needed for things like cmunrm.eot?#iefix,
@@ -110,6 +110,7 @@ getItem userdata f =
exists <- doesFileExist f'
cont <- if exists then B.readFile f' else readDataFile userdata f'
return (cont, mime)
+ where handleErr e = err 61 $ "Failed to retrieve " ++ f ++ "\n" ++ show e
getRaw :: Maybe FilePath -> String -> String -> IO (ByteString, String)
getRaw userdata mimetype src = do
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 09086da1f..0f2e16d2e 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -95,6 +95,7 @@ import Text.Pandoc.MIME (getMimeType)
import System.FilePath ( (>), takeExtension, dropExtension )
import Data.Generics (Typeable, Data)
import qualified Control.Monad.State as S
+import qualified Control.Exception as E
import Control.Monad (msum, unless)
import Text.Pandoc.Pretty (charWidth)
import System.Locale (defaultTimeLocale)
@@ -586,12 +587,13 @@ readDataFileUTF8 userDir fname =
-- | Fetch an image or other item from the local filesystem or the net.
-- Returns raw content and maybe mime type.
-fetchItem :: String -> String -> IO (BS.ByteString, Maybe String)
+fetchItem :: String -> String
+ -> IO (Either E.SomeException (BS.ByteString, Maybe String))
fetchItem sourceDir s =
case s of
_ | isAbsoluteURI s -> openURL s
| isAbsoluteURI sourceDir -> openURL $ sourceDir ++ "/" ++ s
- | otherwise -> do
+ | otherwise -> E.try $ do
let mime = case takeExtension s of
".gz" -> getMimeType $ dropExtension s
x -> getMimeType x
@@ -600,21 +602,21 @@ fetchItem sourceDir s =
return (cont, mime)
-- | Read from a URL and return raw data and maybe mime type.
-openURL :: String -> IO (BS.ByteString, Maybe String)
+openURL :: String -> IO (Either E.SomeException (BS.ByteString, Maybe String))
openURL u
| "data:" `isPrefixOf` u =
let mime = takeWhile (/=',') $ drop 5 u
contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u
- in return (contents, Just mime)
+ in return $ Right (contents, Just mime)
#ifdef HTTP_CONDUIT
- | otherwise = do
+ | otherwise = E.try $ do
req <- parseUrl u
resp <- withManager $ httpLbs req
return (BS.concat $ toChunks $ responseBody resp,
UTF8.toString `fmap` lookup hContentType (responseHeaders resp))
#else
- | otherwise = getBodyAndMimeType `fmap` browse
- (do S.liftIO $ UTF8.hPutStrLn stderr $ "Fetching " ++ u ++ "..."
+ | otherwise = E.try $ getBodyAndMimeType `fmap` browse
+ (do UTF8.hPutStrLn stderr $ "Fetching " ++ u ++ "..."
setOutHandler $ const (return ())
setAllowRedirects True
request (getRequest' u'))
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 1ed8c2fa5..611cddc65 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -726,7 +726,7 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
Just (_,_,_,elt,_) -> return [elt]
Nothing -> do
let sourceDir = writerSourceDirectory opts
- res <- liftIO $ E.try $ fetchItem sourceDir src
+ res <- liftIO $ fetchItem sourceDir src
case res of
Left (_ :: E.SomeException) -> do
liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..."
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index f171a2560..42863ef86 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -123,10 +123,15 @@ writeEPUB opts doc@(Pandoc meta _) = do
Pandoc _ blocks <- bottomUpM
(transformInline opts' sourceDir picsRef) doc
pics <- readIORef picsRef
- let readPicEntry (oldsrc, newsrc) = do
- (img,_) <- fetchItem sourceDir oldsrc
- return $ toEntry newsrc epochtime $ B.fromChunks . (:[]) $ img
- picEntries <- mapM readPicEntry pics
+ let readPicEntry entries (oldsrc, newsrc) = do
+ res <- fetchItem sourceDir oldsrc
+ case res of
+ Left e -> do
+ warn $ "Could not find image `" ++ oldsrc ++ "', skipping..."
+ return entries
+ Right (img,_) -> return $
+ (toEntry newsrc epochtime $ B.fromChunks . (:[]) $ img) : entries
+ picEntries <- foldM readPicEntry [] pics
-- handle fonts
let mkFontEntry f = mkEntry (takeFileName f) `fmap` B.readFile f
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index db27286e8..589010bb9 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -42,7 +42,6 @@ import Text.Pandoc.Definition
import Text.Pandoc.Generic
import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument )
import Control.Monad (liftM)
-import Control.Monad.Trans (liftIO)
import Text.Pandoc.XML
import Text.Pandoc.Pretty
import qualified Control.Exception as E
@@ -114,10 +113,10 @@ writeODT opts doc@(Pandoc meta _) = do
transformPic :: FilePath -> IORef [Entry] -> Inline -> IO Inline
transformPic sourceDir entriesRef (Image lab (src,_)) = do
- res <- liftIO $ E.try $ fetchItem sourceDir src
+ res <- fetchItem sourceDir src
case res of
Left (_ :: E.SomeException) -> do
- liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..."
+ warn $ "Could not find image `" ++ src ++ "', skipping..."
return $ Emph lab
Right (img, _) -> do
let size = imageSize img
--
cgit v1.2.3
From 93e096fe1d23bf60a7ca7fa39fa6e730336338eb Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 18 Jul 2013 21:51:11 -0700
Subject: Fixed warning.
---
src/Text/Pandoc/Writers/EPUB.hs | 2 +-
1 file changed, 1 insertion(+), 1 deletion(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 42863ef86..e625931fc 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -126,7 +126,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
let readPicEntry entries (oldsrc, newsrc) = do
res <- fetchItem sourceDir oldsrc
case res of
- Left e -> do
+ Left _ -> do
warn $ "Could not find image `" ++ oldsrc ++ "', skipping..."
return entries
Right (img,_) -> return $
--
cgit v1.2.3
From d5fad2306a27b3fcf2c85782dd13bc8e516a5df9 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 25 Jul 2013 20:29:42 -0700
Subject: LaTeX writer: Change `\` to `/` in paths.
`/` works even on Windows in LaTeX. `\` will cause major problems
if unescaped.
---
src/Text/Pandoc/Writers/LaTeX.hs | 6 ++++--
1 file changed, 4 insertions(+), 2 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 2b4a608a7..06a04ade2 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -202,7 +202,8 @@ stringToLaTeX ctx (x:xs) = do
_ -> '-' : rest
'~' | not isUrl -> "\\textasciitilde{}" ++ rest
'^' -> "\\^{}" ++ rest
- '\\' -> "\\textbackslash{}" ++ rest
+ '\\'| isUrl -> '/' : rest -- NB. / works as path sep even on Windows
+ | otherwise -> "\\textbackslash{}" ++ rest
'|' -> "\\textbar{}" ++ rest
'<' -> "\\textless{}" ++ rest
'>' -> "\\textgreater{}" ++ rest
@@ -648,7 +649,8 @@ inlineToLaTeX (Image _ (source, _)) = do
let source' = if isAbsoluteURI source
then source
else unEscapeString source
- return $ "\\includegraphics" <> braces (text source')
+ source'' <- stringToLaTeX URLString source'
+ return $ "\\includegraphics" <> braces (text source'')
inlineToLaTeX (Note contents) = do
modify (\s -> s{stInNote = True})
contents' <- blockListToLaTeX contents
--
cgit v1.2.3
From a97f39c12e7b47a272575b69ad4cdd38966c043e Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Fri, 26 Jul 2013 12:40:56 -0700
Subject: Beamer: add allowframebreaks to slide if set in header classes.
It's recommended that your bibliography slide have this
attribute:
# References {.allowframebreaks}
This causes multiple slides to be created if necessary, depending
on the length of the bibliography.
---
README | 10 ++++++++++
src/Text/Pandoc/Writers/LaTeX.hs | 19 +++++++++++--------
2 files changed, 21 insertions(+), 8 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/README b/README
index d9b003344..4895f0f52 100644
--- a/README
+++ b/README
@@ -2674,6 +2674,16 @@ using the `-V` option:
pandoc -t beamer habits.txt -V theme:Warsaw -o habits.pdf
+Note that header attributes will turn into slide attributes
+(on a `` or `
`) in HTML slide formats, allowing you
+to style individual slides. In Beamer, the only header attribute
+that affects slides is the `allowframebreaks` class, which sets the
+`allowframebreaks` option, causing multiple slides to be created
+if the content overfills the frame. This is recommended especially for
+bibliographies:
+
+ # References {.allowframebreaks}
+
Literate Haskell support
========================
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 06a04ade2..aa5bfa623 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -232,7 +232,7 @@ toSlides bs = do
elementToBeamer :: Int -> Element -> State WriterState [Block]
elementToBeamer _slideLevel (Blk b) = return [b]
-elementToBeamer slideLevel (Sec lvl _num (ident,classes,_) tit elts)
+elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts)
| lvl > slideLevel = do
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
return $ Para ( RawInline "latex" "\\begin{block}{"
@@ -240,7 +240,7 @@ elementToBeamer slideLevel (Sec lvl _num (ident,classes,_) tit elts)
: bs ++ [RawBlock "latex" "\\end{block}"]
| lvl < slideLevel = do
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
- return $ (Header lvl (ident,classes,[]) tit) : bs
+ return $ (Header lvl (ident,classes,kvs) tit) : bs
| otherwise = do -- lvl == slideLevel
-- note: [fragile] is required or verbatim breaks
let hasCodeBlock (CodeBlock _ _) = [True]
@@ -248,17 +248,20 @@ elementToBeamer slideLevel (Sec lvl _num (ident,classes,_) tit elts)
let hasCode (Code _ _) = [True]
hasCode _ = []
opts <- gets stOptions
- let fragile = if not $ null $ queryWith hasCodeBlock elts ++
+ let fragile = not $ null $ queryWith hasCodeBlock elts ++
if writerListings opts
then queryWith hasCode elts
else []
- then "[fragile]"
- else ""
- let slideStart = Para $ RawInline "latex" ("\\begin{frame}" ++ fragile) :
+ let allowframebreaks = "allowframebreaks" `elem` classes
+ let optionslist = ["fragile" | fragile] ++
+ ["allowframebreaks" | allowframebreaks]
+ let options = if null optionslist
+ then ""
+ else "[" ++ intercalate "," optionslist ++ "]"
+ let slideStart = Para $ RawInline "latex" ("\\begin{frame}" ++ options) :
if tit == [Str "\0"] -- marker for hrule
then []
- else (RawInline "latex" "\\frametitle{") : tit ++
- [RawInline "latex" "}"]
+ else (RawInline "latex" "{") : tit ++ [RawInline "latex" "}"]
let slideEnd = RawBlock "latex" "\\end{frame}"
-- now carve up slide into blocks if there are sections inside
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
--
cgit v1.2.3
From 4a84b78100f2cfa0f7f7d13a24693a37af60003d Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sat, 3 Aug 2013 23:05:14 -0700
Subject: MediaWiki writer: Use native mediawiki tables instead of HTML.
Closes #720.
---
src/Text/Pandoc/Writers/MediaWiki.hs | 83 +++++----
tests/tables.mediawiki | 316 ++++++++++++++---------------------
2 files changed, 164 insertions(+), 235 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index b3b319c2a..e1bfd18b2 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -36,7 +36,7 @@ import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.XML ( escapeStringForXML )
-import Data.List ( intersect, intercalate )
+import Data.List ( intersect, intercalate, intersperse )
import Network.URI ( isURI )
import Control.Monad.State
@@ -135,25 +135,17 @@ blockToMediaWiki opts (BlockQuote blocks) = do
return $ "" ++ contents ++ "
"
blockToMediaWiki opts (Table capt aligns widths headers rows') = do
- let alignStrings = map alignmentToString aligns
- captionDoc <- if null capt
- then return ""
- else do
- c <- inlineListToMediaWiki opts capt
- return $ "" ++ c ++ "\n"
- let percent w = show (truncate (100*w) :: Integer) ++ "%"
- let coltags = if all (== 0.0) widths
- then ""
- else unlines $ map
- (\w -> "") widths
- head' <- if all null headers
- then return ""
- else do
- hs <- tableRowToMediaWiki opts alignStrings 0 headers
- return $ "\n" ++ hs ++ "\n\n"
- body' <- zipWithM (tableRowToMediaWiki opts alignStrings) [1..] rows'
- return $ "\n" ++ captionDoc ++ coltags ++ head' ++
- "\n" ++ unlines body' ++ "\n
\n"
+ caption <- if null capt
+ then return ""
+ else do
+ c <- inlineListToMediaWiki opts capt
+ return $ "|+ " ++ trimr c ++ "\n"
+ let headless = all null headers
+ let allrows = if headless then rows' else headers:rows'
+ tableBody <- (concat . intersperse "|-\n") `fmap`
+ mapM (tableRowToMediaWiki opts headless aligns widths)
+ (zip [1..] allrows)
+ return $ "{|\n" ++ caption ++ tableBody ++ "|}\n"
blockToMediaWiki opts x@(BulletList items) = do
oldUseTags <- get >>= return . stUseTags
@@ -285,20 +277,34 @@ vcat = intercalate "\n"
-- Auxiliary functions for tables:
tableRowToMediaWiki :: WriterOptions
- -> [String]
- -> Int
- -> [[Block]]
+ -> Bool
+ -> [Alignment]
+ -> [Double]
+ -> (Int, [[Block]])
-> State WriterState String
-tableRowToMediaWiki opts alignStrings rownum cols' = do
- let celltype = if rownum == 0 then "th" else "td"
- let rowclass = case rownum of
- 0 -> "header"
- x | x `rem` 2 == 1 -> "odd"
- _ -> "even"
- cols'' <- sequence $ zipWith
- (\alignment item -> tableItemToMediaWiki opts celltype alignment item)
- alignStrings cols'
- return $ "\n" ++ unlines cols'' ++ "
"
+tableRowToMediaWiki opts headless alignments widths (rownum, cells) = do
+ cells' <- mapM (\cellData ->
+ tableCellToMediaWiki opts headless rownum cellData)
+ $ zip3 alignments widths cells
+ return $ unlines cells'
+
+tableCellToMediaWiki :: WriterOptions
+ -> Bool
+ -> Int
+ -> (Alignment, Double, [Block])
+ -> State WriterState String
+tableCellToMediaWiki opts headless rownum (alignment, width, bs) = do
+ contents <- blockListToMediaWiki opts bs
+ let marker = if rownum == 1 && not headless then "!" else "|"
+ let percent w = show (truncate (100*w) :: Integer) ++ "%"
+ let attrs = ["align=" ++ show (alignmentToString alignment) |
+ alignment /= AlignDefault && alignment /= AlignLeft] ++
+ ["width=\"" ++ percent width ++ "\"" |
+ width /= 0.0 && rownum == 1]
+ let attr = if null attrs
+ then ""
+ else unwords attrs ++ "|"
+ return $ marker ++ attr ++ trimr contents
alignmentToString :: Alignment -> [Char]
alignmentToString alignment = case alignment of
@@ -307,17 +313,6 @@ alignmentToString alignment = case alignment of
AlignCenter -> "center"
AlignDefault -> "left"
-tableItemToMediaWiki :: WriterOptions
- -> String
- -> String
- -> [Block]
- -> State WriterState String
-tableItemToMediaWiki opts celltype align' item = do
- let mkcell x = "<" ++ celltype ++ " align=\"" ++ align' ++ "\">" ++
- x ++ "" ++ celltype ++ ">"
- contents <- blockListToMediaWiki opts item
- return $ mkcell contents
-
-- | Convert list of Pandoc block elements to MediaWiki.
blockListToMediaWiki :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
diff --git a/tests/tables.mediawiki b/tests/tables.mediawiki
index 4836ecd79..efde76559 100644
--- a/tests/tables.mediawiki
+++ b/tests/tables.mediawiki
@@ -1,212 +1,146 @@
Simple table with caption:
-
-Demonstration of simple table syntax.
-
-
-
-
-
-| 12 |
-12 |
-12 |
-12 |
-
-
-| 123 |
-123 |
-123 |
-123 |
-
-
-| 1 |
-1 |
-1 |
-1 |
-
-
-
+{|
+|+ Demonstration of simple table syntax.
+!align="right"|Right
+!Left
+!align="center"|Center
+!Default
+|-
+|align="right"|12
+|12
+|align="center"|12
+|12
+|-
+|align="right"|123
+|123
+|align="center"|123
+|123
+|-
+|align="right"|1
+|1
+|align="center"|1
+|1
+|}
Simple table without caption:
-
-
-
-
-
-
-| 12 |
-12 |
-12 |
-12 |
-
-
-| 123 |
-123 |
-123 |
-123 |
-
-
-| 1 |
-1 |
-1 |
-1 |
-
-
-
+{|
+!align="right"|Right
+!Left
+!align="center"|Center
+!Default
+|-
+|align="right"|12
+|12
+|align="center"|12
+|12
+|-
+|align="right"|123
+|123
+|align="center"|123
+|123
+|-
+|align="right"|1
+|1
+|align="center"|1
+|1
+|}
Simple table indented two spaces:
-
-Demonstration of simple table syntax.
-
-
-
-
-
-| 12 |
-12 |
-12 |
-12 |
-
-
-| 123 |
-123 |
-123 |
-123 |
-
-
-| 1 |
-1 |
-1 |
-1 |
-
-
-
+{|
+|+ Demonstration of simple table syntax.
+!align="right"|Right
+!Left
+!align="center"|Center
+!Default
+|-
+|align="right"|12
+|12
+|align="center"|12
+|12
+|-
+|align="right"|123
+|123
+|align="center"|123
+|123
+|-
+|align="right"|1
+|1
+|align="center"|1
+|1
+|}
Multiline table with caption:
-
-Here's the caption. It may span multiple lines.
-
-
-
-
-
-
-
-
-
-| First |
-row |
-12.0 |
-Example of a row that spans multiple lines. |
-
-
-| Second |
-row |
-5.0 |
-Here's another one. Note the blank line between rows. |
-
-
-
+{|
+|+ Here's the caption. It may span multiple lines.
+!align="center" width="15%"|Centered Header
+!width="13%"|Left Aligned
+!align="right" width="16%"|Right Aligned
+!width="33%"|Default aligned
+|-
+|align="center"|First
+|row
+|align="right"|12.0
+|Example of a row that spans multiple lines.
+|-
+|align="center"|Second
+|row
+|align="right"|5.0
+|Here's another one. Note the blank line between rows.
+|}
Multiline table without caption:
-
-
-
-
-
-
-
-
-
-
-| First |
-row |
-12.0 |
-Example of a row that spans multiple lines. |
-
-
-| Second |
-row |
-5.0 |
-Here's another one. Note the blank line between rows. |
-
-
-
+{|
+!align="center" width="15%"|Centered Header
+!width="13%"|Left Aligned
+!align="right" width="16%"|Right Aligned
+!width="33%"|Default aligned
+|-
+|align="center"|First
+|row
+|align="right"|12.0
+|Example of a row that spans multiple lines.
+|-
+|align="center"|Second
+|row
+|align="right"|5.0
+|Here's another one. Note the blank line between rows.
+|}
Table without column headers:
-
-
-
-| 12 |
-12 |
-12 |
-12 |
-
-
-| 123 |
-123 |
-123 |
-123 |
-
-
-| 1 |
-1 |
-1 |
-1 |
-
-
-
+{|
+|align="right"|12
+|12
+|align="center"|12
+|align="right"|12
+|-
+|align="right"|123
+|123
+|align="center"|123
+|align="right"|123
+|-
+|align="right"|1
+|1
+|align="center"|1
+|align="right"|1
+|}
Multiline table without column headers:
-
-
-
-
-
-
-
-| First |
-row |
-12.0 |
-Example of a row that spans multiple lines. |
-
-
-| Second |
-row |
-5.0 |
-Here's another one. Note the blank line between rows. |
-
-
-
+{|
+|align="center" width="15%"|First
+|width="13%"|row
+|align="right" width="16%"|12.0
+|width="33%"|Example of a row that spans multiple lines.
+|-
+|align="center"|Second
+|row
+|align="right"|5.0
+|Here's another one. Note the blank line between rows.
+|}
--
cgit v1.2.3
From 2d6e0b1530e61fa2d6a22d8b61042734b20f0af5 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 4 Aug 2013 14:12:13 -0700
Subject: Remove CPP from default-extensions; add pragmas to modules as needed.
---
man/make-pandoc-man-pages.hs | 1 +
pandoc.cabal | 4 ----
src/Text/Pandoc/Pretty.hs | 2 +-
src/Text/Pandoc/UTF8.hs | 1 +
src/Text/Pandoc/Writers/EPUB.hs | 6 +-----
5 files changed, 4 insertions(+), 10 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/man/make-pandoc-man-pages.hs b/man/make-pandoc-man-pages.hs
index eca1276eb..008294433 100644
--- a/man/make-pandoc-man-pages.hs
+++ b/man/make-pandoc-man-pages.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
-- Create pandoc.1 man and pandoc_markdown.5 man pages from README
import Text.Pandoc
import qualified Text.Pandoc.UTF8 as UTF8
diff --git a/pandoc.cabal b/pandoc.cabal
index 7d4bccc41..7f12a44ae 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -277,7 +277,6 @@ Library
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
Ghc-Prof-Options: -auto-all -caf-all -rtsopts
Default-Language: Haskell98
- Default-Extensions: CPP
Other-Extensions: PatternGuards, OverloadedStrings,
ScopedTypeVariables, GeneralizedNewtypeDeriving,
RelaxedPolyRec, DeriveDataTypeable, TypeSynonymInstances,
@@ -357,7 +356,6 @@ Executable pandoc
if os(windows)
Cpp-options: -D_WINDOWS
Default-Language: Haskell98
- Default-Extensions: CPP
Other-Extensions: PatternGuards, OverloadedStrings,
ScopedTypeVariables, GeneralizedNewtypeDeriving,
RelaxedPolyRec, DeriveDataTypeable, TypeSynonymInstances,
@@ -377,7 +375,6 @@ Executable make-pandoc-man-pages
old-time >= 1.0 && < 1.2,
time >= 1.2 && < 1.5
Default-Language: Haskell98
- Default-Extensions: CPP
Test-Suite test-pandoc
Type: exitcode-stdio-1.0
@@ -415,7 +412,6 @@ Test-Suite test-pandoc
Tests.Writers.LaTeX
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
Default-Language: Haskell98
- Default-Extensions: CPP
benchmark benchmark-pandoc
Type: exitcode-stdio-1.0
diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs
index 21121a506..faf2a6797 100644
--- a/src/Text/Pandoc/Pretty.hs
+++ b/src/Text/Pandoc/Pretty.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving, CPP #-}
{-
Copyright (C) 2010 John MacFarlane
diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs
index 9fa743cd9..229442543 100644
--- a/src/Text/Pandoc/UTF8.hs
+++ b/src/Text/Pandoc/UTF8.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
{-
Copyright (C) 2010 John MacFarlane
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index e625931fc..fb756f196 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE PatternGuards, CPP #-}
{-
Copyright (C) 2010 John MacFarlane
@@ -62,11 +62,7 @@ import Text.Pandoc.MIME (getMimeType)
import Prelude hiding (catch)
#endif
import Control.Exception (catch, SomeException)
-#if MIN_VERSION_blaze_html(0,5,0)
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
-#else
-import Text.Blaze.Renderer.Utf8 (renderHtml)
-#endif
-- A Chapter includes a list of blocks and maybe a section
-- number offset. Note, some chapters are unnumbered. The section
--
cgit v1.2.3
From 7d18770b008c12e13c324223304c6703e06f3a4a Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Tue, 6 Aug 2013 23:31:01 -0700
Subject: Added support for MetaBool.
---
src/Text/Pandoc/Readers/Markdown.hs | 2 +-
src/Text/Pandoc/Writers/Custom.hs | 2 ++
src/Text/Pandoc/Writers/Shared.hs | 1 +
3 files changed, 4 insertions(+), 1 deletion(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 076706b4e..a880c09de 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -278,7 +278,7 @@ toMetaValue opts x =
yamlToMeta :: ReaderOptions -> Yaml.Value -> MetaValue
yamlToMeta opts (Yaml.String t) = toMetaValue opts t
yamlToMeta _ (Yaml.Number n) = MetaString $ show n
-yamlToMeta _ (Yaml.Bool b) = MetaString $ map toLower $ show b
+yamlToMeta _ (Yaml.Bool b) = MetaBool b
yamlToMeta opts (Yaml.Array xs) = B.toMetaValue $ map (yamlToMeta opts)
$ V.toList xs
yamlToMeta opts (Yaml.Object o) = MetaMap $ H.foldrWithKey (\k v m ->
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 732497616..5c82fe0e1 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -110,12 +110,14 @@ instance StackValue [Block] where
instance StackValue MetaValue where
push l (MetaMap m) = Lua.push l m
push l (MetaList xs) = Lua.push l xs
+ push l (MetaBool x) = Lua.push l x
push l (MetaString s) = Lua.push l s
push l (MetaInlines ils) = Lua.push l ils
push l (MetaBlocks bs) = Lua.push l bs
peek _ _ = undefined
valuetype (MetaMap _) = Lua.TTABLE
valuetype (MetaList _) = Lua.TTABLE
+ valuetype (MetaBool _) = Lua.TBOOLEAN
valuetype (MetaString _) = Lua.TSTRING
valuetype (MetaInlines _) = Lua.TSTRING
valuetype (MetaBlocks _) = Lua.TSTRING
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index c6c30d070..e6ec853f8 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -74,6 +74,7 @@ metaValueToJSON blockWriter inlineWriter (MetaMap metamap) = liftM toJSON $
Traversable.mapM (metaValueToJSON blockWriter inlineWriter) metamap
metaValueToJSON blockWriter inlineWriter (MetaList xs) = liftM toJSON $
Traversable.mapM (metaValueToJSON blockWriter inlineWriter) xs
+metaValueToJSON _ _ (MetaBool b) = return $ toJSON b
metaValueToJSON _ _ (MetaString s) = return $ toJSON s
metaValueToJSON blockWriter _ (MetaBlocks bs) = liftM toJSON $ blockWriter bs
metaValueToJSON _ inlineWriter (MetaInlines bs) = liftM toJSON $ inlineWriter bs
--
cgit v1.2.3
From 802dc9a8b9f206eb3be592ab19067f637eb2a3ee Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 8 Aug 2013 10:41:39 -0700
Subject: Added Text.Pandoc.Compat.Monoid.
This allows pandoc to compile with base < 4.5, where Data.Monoid
doesn't export `<>`. Thanks to Dirk Ullirch for the patch.
---
pandoc.cabal | 1 +
src/Text/Pandoc/Compat/Monoid.hs | 16 ++++++++++++++++
src/Text/Pandoc/Templates.hs | 2 +-
src/Text/Pandoc/Writers/Docx.hs | 2 +-
4 files changed, 19 insertions(+), 2 deletions(-)
create mode 100644 src/Text/Pandoc/Compat/Monoid.hs
(limited to 'src/Text/Pandoc/Writers')
diff --git a/pandoc.cabal b/pandoc.cabal
index 3dc400d40..192b6c5fd 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -335,6 +335,7 @@ Library
Text.Pandoc.ImageSize,
Text.Pandoc.Slides,
Text.Pandoc.Highlighting,
+ Text.Pandoc.Compat.Monoid,
Paths_pandoc
Buildable: True
diff --git a/src/Text/Pandoc/Compat/Monoid.hs b/src/Text/Pandoc/Compat/Monoid.hs
new file mode 100644
index 000000000..80ffcbbd6
--- /dev/null
+++ b/src/Text/Pandoc/Compat/Monoid.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE CPP #-}
+module Text.Pandoc.Compat.Monoid ( Monoid(..)
+ , (<>)
+ ) where
+
+#if MIN_VERSION_base(4,5,0)
+import Data.Monoid ((<>), Monoid(..))
+#else
+import Data.Monoid (mappend, Monoid(..))
+#endif
+
+#if MIN_VERSION_base(4,5,0)
+#else
+(<>) :: Monoid m => m -> m -> m
+(<>) = mappend
+#endif
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index c95c84ca8..22a44e735 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -102,7 +102,7 @@ import Control.Applicative
import qualified Data.Text as T
import Data.Text (Text)
import Data.Text.Encoding (encodeUtf8)
-import Data.Monoid ((<>), Monoid(..))
+import Text.Pandoc.Compat.Monoid ((<>), Monoid(..))
import Data.List (intersperse, nub)
import System.FilePath ((>), (<.>))
import qualified Data.Map as M
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 611cddc65..6bb4d5569 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -35,7 +35,7 @@ import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL8
import qualified Data.Map as M
import qualified Text.Pandoc.UTF8 as UTF8
-import Data.Monoid ((<>))
+import Text.Pandoc.Compat.Monoid ((<>))
import Codec.Archive.Zip
import Data.Time.Clock.POSIX
import Text.Pandoc.Definition
--
cgit v1.2.3
From e9de0f0e22b9b64b5684efe81d03539c3f57a71c Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 8 Aug 2013 23:14:12 -0700
Subject: Preliminary support for new Div and Span elements in writers.
Currently these are "transparent" containers, except in HTML,
where they produce div and span elements with attributes.
---
data/sample.lua | 8 ++++++++
src/Text/Pandoc/Writers/AsciiDoc.hs | 2 ++
src/Text/Pandoc/Writers/ConTeXt.hs | 2 ++
src/Text/Pandoc/Writers/Custom.hs | 5 +++++
src/Text/Pandoc/Writers/Docbook.hs | 3 +++
src/Text/Pandoc/Writers/Docx.hs | 2 ++
src/Text/Pandoc/Writers/FB2.hs | 3 +++
src/Text/Pandoc/Writers/HTML.hs | 5 +++++
src/Text/Pandoc/Writers/LaTeX.hs | 2 ++
src/Text/Pandoc/Writers/Man.hs | 2 ++
src/Text/Pandoc/Writers/Markdown.hs | 3 +++
src/Text/Pandoc/Writers/MediaWiki.hs | 6 ++++++
src/Text/Pandoc/Writers/OpenDocument.hs | 2 ++
src/Text/Pandoc/Writers/Org.hs | 3 +++
src/Text/Pandoc/Writers/RST.hs | 2 ++
src/Text/Pandoc/Writers/RTF.hs | 3 +++
src/Text/Pandoc/Writers/Texinfo.hs | 5 +++++
src/Text/Pandoc/Writers/Textile.hs | 6 ++++++
18 files changed, 64 insertions(+)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/data/sample.lua b/data/sample.lua
index 1c82ebe2e..a7e9d6337 100644
--- a/data/sample.lua
+++ b/data/sample.lua
@@ -177,6 +177,10 @@ function Note(s)
'">' .. num .. ''
end
+function Span(s, attr)
+ return "" .. s .. ""
+end
+
function Plain(s)
return s
end
@@ -299,6 +303,10 @@ function Table(caption, aligns, widths, headers, rows)
return table.concat(buffer,'\n')
end
+function Div(s, attr)
+ return "\n" .. s .. "
"
+end
+
-- The following code will produce runtime warnings when you haven't defined
-- all of the functions you need for the custom writer, so it's useful
-- to include when you're working on a writer.
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 6c3c6955e..00cea27e5 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -246,6 +246,7 @@ blockToAsciiDoc opts (OrderedList (_start, sty, _delim) items) = do
blockToAsciiDoc opts (DefinitionList items) = do
contents <- mapM (definitionListItemToAsciiDoc opts) items
return $ cat contents <> blankline
+blockToAsciiDoc opts (Div _ bs) = blockListToAsciiDoc opts bs
-- | Convert bullet list item (list of blocks) to asciidoc.
bulletListItemToAsciiDoc :: WriterOptions -> [Block] -> State WriterState Doc
@@ -383,3 +384,4 @@ inlineToAsciiDoc opts (Note [Plain inlines]) = do
return $ text "footnote:[" <> contents <> "]"
-- asciidoc can't handle blank lines in notes
inlineToAsciiDoc _ (Note _) = return "[multiblock footnote omitted]"
+inlineToAsciiDoc opts (Span _ ils) = inlineListToAsciiDoc opts ils
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 32588dc8f..40dc1deb5 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -143,6 +143,7 @@ blockToConTeXt (CodeBlock _ str) =
-- blankline because \stoptyping can't have anything after it, inc. '}'
blockToConTeXt (RawBlock "context" str) = return $ text str <> blankline
blockToConTeXt (RawBlock _ _ ) = return empty
+blockToConTeXt (Div _ bs) = blockListToConTeXt bs
blockToConTeXt (BulletList lst) = do
contents <- mapM listItemToConTeXt lst
return $ ("\\startitemize" <> if isTightList lst
@@ -330,6 +331,7 @@ inlineToConTeXt (Note contents) = do
then text "\\footnote{" <> nest 2 contents' <> char '}'
else text "\\startbuffer " <> nest 2 contents' <>
text "\\stopbuffer\\footnote{\\getbuffer}"
+inlineToConTeXt (Span _ ils) = inlineListToConTeXt ils
-- | Craft the section header, inserting the secton reference, if supplied.
sectionHeader :: Attr
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 5c82fe0e1..c250a240e 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -178,6 +178,9 @@ blockToCustom lua (OrderedList (num,sty,delim) items) =
blockToCustom lua (DefinitionList items) =
callfunc lua "DefinitionList" items
+blockToCustom lua (Div attr items) =
+ callfunc lua "Div" items (attrToMap attr)
+
-- | Convert list of Pandoc block elements to Custom.
blockListToCustom :: LuaState -- ^ Options
-> [Block] -- ^ List of block elements
@@ -240,3 +243,5 @@ inlineToCustom lua (Image alt (src,tit)) =
inlineToCustom lua (Note contents) = callfunc lua "Note" contents
+inlineToCustom lua (Span attr items) =
+ callfunc lua "Span" items (attrToMap attr)
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 6f4b61a79..2f415f3ee 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -148,6 +148,7 @@ listItemToDocbook opts item =
-- | Convert a Pandoc block element to Docbook.
blockToDocbook :: WriterOptions -> Block -> Doc
blockToDocbook _ Null = empty
+blockToDocbook opts (Div _ bs) = blocksToDocbook opts bs
blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
-- title beginning with fig: indicates that the image is a figure
@@ -267,6 +268,8 @@ inlineToDocbook opts (Quoted _ lst) =
inTagsSimple "quote" $ inlinesToDocbook opts lst
inlineToDocbook opts (Cite _ lst) =
inlinesToDocbook opts lst
+inlineToDocbook opts (Span _ ils) =
+ inlinesToDocbook opts ils
inlineToDocbook _ (Code _ str) =
inTagsSimple "literal" $ text (escapeStringForXML str)
inlineToDocbook opts (Math t str)
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 6bb4d5569..d93254971 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -428,6 +428,7 @@ getUniqueId = liftIO $ (show . (+ 20) . hashUnique) `fmap` newUnique
-- | Convert a Pandoc block element to OpenXML.
blockToOpenXML :: WriterOptions -> Block -> WS [Element]
blockToOpenXML _ Null = return []
+blockToOpenXML opts (Div _ bs) = blocksToOpenXML opts bs
blockToOpenXML opts (Header lev (ident,_,_) lst) = do
contents <- withParaProp (pStyle $ "Heading" ++ show lev) $
blockToOpenXML opts (Para lst)
@@ -633,6 +634,7 @@ formattedString str = do
inlineToOpenXML :: WriterOptions -> Inline -> WS [Element]
inlineToOpenXML _ (Str str) = formattedString str
inlineToOpenXML opts Space = inlineToOpenXML opts (Str " ")
+inlineToOpenXML opts (Span _ ils) = inlinesToOpenXML opts ils
inlineToOpenXML opts (Strong lst) =
withTextProp (mknode "w:b" [] ()) $ inlinesToOpenXML opts lst
inlineToOpenXML opts (Emph lst) =
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 27f0c8305..2576b2dc2 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -324,6 +324,7 @@ blockToXml (CodeBlock _ s) = return . spaceBeforeAfter .
map (el "p" . el "code") . lines $ s
blockToXml (RawBlock _ s) = return . spaceBeforeAfter .
map (el "p" . el "code") . lines $ s
+blockToXml (Div _ bs) = cMapM blockToXml bs
blockToXml (BlockQuote bs) = liftM (list . el "cite") $ cMapM blockToXml bs
blockToXml (OrderedList a bss) = do
state <- get
@@ -425,6 +426,7 @@ indent = indentBlock
-- | Convert a Pandoc's Inline element to FictionBook XML representation.
toXml :: Inline -> FBM [Content]
toXml (Str s) = return [txt s]
+toXml (Span _ ils) = cMapM toXml ils
toXml (Emph ss) = list `liftM` wrap "emphasis" ss
toXml (Strong ss) = list `liftM` wrap "strong" ss
toXml (Strikeout ss) = list `liftM` wrap "strikethrough" ss
@@ -560,6 +562,7 @@ list = (:[])
plain :: Inline -> String
plain (Str s) = s
plain (Emph ss) = concat (map plain ss)
+plain (Span _ ss) = concat (map plain ss)
plain (Strong ss) = concat (map plain ss)
plain (Strikeout ss) = concat (map plain ss)
plain (Superscript ss) = concat (map plain ss)
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index cfc187e02..560c26c76 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -407,6 +407,9 @@ blockToHtml opts (Para [Str ".",Space,Str ".",Space,Str "."])
blockToHtml opts (Para lst) = do
contents <- inlineListToHtml opts lst
return $ H.p contents
+blockToHtml opts (Div attr bs) = do
+ contents <- blockListToHtml opts bs
+ return $ addAttrs opts attr $ H.div $ nl opts >> contents >> nl opts
blockToHtml _ (RawBlock "html" str) = return $ preEscapedString str
blockToHtml _ (RawBlock _ _) = return mempty
blockToHtml opts (HorizontalRule) = return $ if writerHtml5 opts then H5.hr else H.hr
@@ -590,6 +593,8 @@ inlineToHtml opts inline =
(Str str) -> return $ strToHtml str
(Space) -> return $ strToHtml " "
(LineBreak) -> return $ if writerHtml5 opts then H5.br else H.br
+ (Span attr ils) -> inlineListToHtml opts ils >>=
+ return . addAttrs opts attr . H.span
(Emph lst) -> inlineListToHtml opts lst >>= return . H.em
(Strong lst) -> inlineListToHtml opts lst >>= return . H.strong
(Code attr str) -> case hlCode of
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index aa5bfa623..37de03e0f 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -282,6 +282,7 @@ isLineBreakOrSpace _ = False
blockToLaTeX :: Block -- ^ Block to convert
-> State WriterState Doc
blockToLaTeX Null = return empty
+blockToLaTeX (Div _ bs) = blockListToLaTeX bs
blockToLaTeX (Plain lst) =
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
-- title beginning with fig: indicates that the image is a figure
@@ -560,6 +561,7 @@ isQuoted _ = False
-- | Convert inline element to LaTeX
inlineToLaTeX :: Inline -- ^ Inline to convert
-> State WriterState Doc
+inlineToLaTeX (Span _ ils) = inlineListToLaTeX ils >>= return . braces
inlineToLaTeX (Emph lst) =
inlineListToLaTeX lst >>= return . inCmd "emph"
inlineToLaTeX (Strong lst) =
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 0508b6c27..ed66c7c2b 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -160,6 +160,7 @@ blockToMan :: WriterOptions -- ^ Options
-> Block -- ^ Block element
-> State WriterState Doc
blockToMan _ Null = return empty
+blockToMan opts (Div _ bs) = blockListToMan opts bs
blockToMan opts (Plain inlines) =
liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines
blockToMan opts (Para inlines) = do
@@ -300,6 +301,7 @@ inlineListToMan opts lst = mapM (inlineToMan opts) lst >>= (return . hcat)
-- | Convert Pandoc inline element to man.
inlineToMan :: WriterOptions -> Inline -> State WriterState Doc
+inlineToMan opts (Span _ ils) = inlineListToMan opts ils
inlineToMan opts (Emph lst) = do
contents <- inlineListToMan opts lst
return $ text "\\f[I]" <> contents <> text "\\f[]"
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 80402a757..d195d8445 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -301,6 +301,7 @@ blockToMarkdown :: WriterOptions -- ^ Options
-> Block -- ^ Block element
-> State WriterState Doc
blockToMarkdown _ Null = return empty
+blockToMarkdown opts (Div _ bs) = blockListToMarkdown opts bs
blockToMarkdown opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
return $ contents <> cr
@@ -628,6 +629,8 @@ escapeSpaces x = x
-- | Convert Pandoc inline element to markdown.
inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc
+inlineToMarkdown opts (Span _ ils) =
+ inlineListToMarkdown opts ils
inlineToMarkdown opts (Emph lst) = do
contents <- inlineListToMarkdown opts lst
return $ "*" <> contents <> "*"
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index e1bfd18b2..fccf25753 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -83,6 +83,9 @@ blockToMediaWiki :: WriterOptions -- ^ Options
blockToMediaWiki _ Null = return ""
+blockToMediaWiki opts (Div _ bs) =
+ blockListToMediaWiki opts bs
+
blockToMediaWiki opts (Plain inlines) =
inlineListToMediaWiki opts inlines
@@ -328,6 +331,9 @@ inlineListToMediaWiki opts lst =
-- | Convert Pandoc inline element to MediaWiki.
inlineToMediaWiki :: WriterOptions -> Inline -> State WriterState String
+inlineToMediaWiki opts (Span _ ils) =
+ inlineListToMediaWiki opts ils
+
inlineToMediaWiki opts (Emph lst) = do
contents <- inlineListToMediaWiki opts lst
return $ "''" ++ contents ++ "''"
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 0efbf7580..d76d0f6ad 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -285,6 +285,7 @@ blockToOpenDocument :: WriterOptions -> Block -> State WriterState Doc
blockToOpenDocument o bs
| Plain b <- bs = inParagraphTags =<< inlinesToOpenDocument o b
| Para b <- bs = inParagraphTags =<< inlinesToOpenDocument o b
+ | Div _ xs <- bs = blocksToOpenDocument o xs
| Header i _ b <- bs = setFirstPara >>
(inHeaderTags i =<< inlinesToOpenDocument o b)
| BlockQuote b <- bs = setFirstPara >> mkBlockQuote b
@@ -360,6 +361,7 @@ inlinesToOpenDocument o l = hcat <$> mapM (inlineToOpenDocument o) l
inlineToOpenDocument :: WriterOptions -> Inline -> State WriterState Doc
inlineToOpenDocument o ils
| Space <- ils = inTextStyle space
+ | Span _ xs <- ils = inlinesToOpenDocument o xs
| LineBreak <- ils = return $ selfClosingTag "text:line-break" []
| Str s <- ils = inTextStyle $ handleSpaces $ escapeStringForXML s
| Emph l <- ils = withTextStyle Italic $ inlinesToOpenDocument o l
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 40e8abf7e..34ae532b0 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -106,6 +106,7 @@ escapeString = escapeStringUsing $
blockToOrg :: Block -- ^ Block element
-> State WriterState Doc
blockToOrg Null = return empty
+blockToOrg (Div _ bs) = blockListToOrg bs
blockToOrg (Plain inlines) = inlineListToOrg inlines
-- title beginning with fig: indicates that the image is a figure
blockToOrg (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
@@ -229,6 +230,8 @@ inlineListToOrg lst = mapM inlineToOrg lst >>= return . hcat
-- | Convert Pandoc inline element to Org.
inlineToOrg :: Inline -> State WriterState Doc
+inlineToOrg (Span _ lst) =
+ inlineListToOrg lst
inlineToOrg (Emph lst) = do
contents <- inlineListToOrg lst
return $ "/" <> contents <> "/"
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 606793842..4d8daa15b 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -161,6 +161,7 @@ bordered contents c =
blockToRST :: Block -- ^ Block element
-> State WriterState Doc
blockToRST Null = return empty
+blockToRST (Div _ bs) = blockListToRST bs
blockToRST (Plain inlines) = inlineListToRST inlines
-- title beginning with fig: indicates that the image is a figure
blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
@@ -338,6 +339,7 @@ inlineListToRST lst = mapM inlineToRST (insertBS lst) >>= return . hcat
-- | Convert Pandoc inline element to RST.
inlineToRST :: Inline -> State WriterState Doc
+inlineToRST (Span _ ils) = inlineListToRST ils
inlineToRST (Emph lst) = do
contents <- inlineListToRST lst
return $ "*" <> contents <> "*"
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 0db1c52c4..7e5d33c50 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -208,6 +208,8 @@ blockToRTF :: Int -- ^ indent level
-> Block -- ^ block to convert
-> String
blockToRTF _ _ Null = ""
+blockToRTF indent alignment (Div _ bs) =
+ concatMap (blockToRTF indent alignment) bs
blockToRTF indent alignment (Plain lst) =
rtfCompact indent 0 alignment $ inlineListToRTF lst
blockToRTF indent alignment (Para lst) =
@@ -308,6 +310,7 @@ inlineListToRTF lst = concatMap inlineToRTF lst
-- | Convert inline item to RTF.
inlineToRTF :: Inline -- ^ inline to convert
-> String
+inlineToRTF (Span _ lst) = inlineListToRTF lst
inlineToRTF (Emph lst) = "{\\i " ++ (inlineListToRTF lst) ++ "}"
inlineToRTF (Strong lst) = "{\\b " ++ (inlineListToRTF lst) ++ "}"
inlineToRTF (Strikeout lst) = "{\\strike " ++ (inlineListToRTF lst) ++ "}"
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 0f57d14b2..f8b460001 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -123,6 +123,8 @@ blockToTexinfo :: Block -- ^ Block to convert
blockToTexinfo Null = return empty
+blockToTexinfo (Div _ bs) = blockListToTexinfo bs
+
blockToTexinfo (Plain lst) =
inlineListToTexinfo lst
@@ -374,6 +376,9 @@ disallowedInNode c = c `elem` ".,:()"
inlineToTexinfo :: Inline -- ^ Inline to convert
-> State WriterState Doc
+inlineToTexinfo (Span _ lst) =
+ inlineListToTexinfo lst
+
inlineToTexinfo (Emph lst) =
inlineListToTexinfo lst >>= return . inCmd "emph"
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 3288ce222..3fb554dca 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -101,6 +101,9 @@ blockToTextile :: WriterOptions -- ^ Options
blockToTextile _ Null = return ""
+blockToTextile opts (Div _ bs) =
+ blockListToTextile opts bs
+
blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines
@@ -343,6 +346,9 @@ inlineListToTextile opts lst =
-- | Convert Pandoc inline element to Textile.
inlineToTextile :: WriterOptions -> Inline -> State WriterState String
+inlineToTextile opts (Span _ lst) =
+ inlineListToTextile opts lst
+
inlineToTextile opts (Emph lst) = do
contents <- inlineListToTextile opts lst
return $ if '_' `elem` contents
--
cgit v1.2.3
From cbfa9321066212b912583481015224f3c944ae21 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sat, 10 Aug 2013 17:23:51 -0700
Subject: Adjustments for new Format newtype.
---
src/Text/Pandoc/Readers/HTML.hs | 4 ++--
src/Text/Pandoc/Readers/LaTeX.hs | 2 +-
src/Text/Pandoc/Readers/RST.hs | 1 +
src/Text/Pandoc/Readers/Textile.hs | 6 +++---
src/Text/Pandoc/Writers/AsciiDoc.hs | 8 ++++++--
src/Text/Pandoc/Writers/Custom.hs | 6 ++++++
src/Text/Pandoc/Writers/Docbook.hs | 9 +++++----
src/Text/Pandoc/Writers/Docx.hs | 10 +++++-----
src/Text/Pandoc/Writers/EPUB.hs | 6 +++---
src/Text/Pandoc/Writers/HTML.hs | 13 ++++++++-----
src/Text/Pandoc/Writers/LaTeX.hs | 13 ++++++++-----
src/Text/Pandoc/Writers/Man.hs | 10 ++++++----
src/Text/Pandoc/Writers/MediaWiki.hs | 14 ++++++++------
src/Text/Pandoc/Writers/OpenDocument.hs | 12 +++++++-----
src/Text/Pandoc/Writers/RST.hs | 15 +++++++++------
src/Text/Pandoc/Writers/RTF.hs | 12 +++++++-----
src/Text/Pandoc/Writers/Texinfo.hs | 19 +++++++++++--------
src/Text/Pandoc/Writers/Textile.hs | 14 ++++++--------
tests/Tests/Arbitrary.hs | 8 ++++----
19 files changed, 106 insertions(+), 76 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 0068ab5c1..7ca554fa3 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -182,7 +182,7 @@ pRawHtmlBlock = do
raw <- pHtmlBlock "script" <|> pHtmlBlock "style" <|> pRawTag
parseRaw <- getOption readerParseRaw
if parseRaw && not (null raw)
- then return [RawBlock "html" raw]
+ then return [RawBlock (Format "html") raw]
else return []
pHtmlBlock :: String -> TagParser String
@@ -408,7 +408,7 @@ pRawHtmlInline = do
result <- pSatisfy (tagComment (const True)) <|> pSatisfy isInlineTag
parseRaw <- getOption readerParseRaw
if parseRaw
- then return [RawInline "html" $ renderTags' [result]]
+ then return [RawInline (Format "html") $ renderTags' [result]]
else return []
pInlinesInTags :: String -> ([Inline] -> Inline)
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 6b5035d93..eb0baedda 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE ScopedTypeVariables, OverloadedStrings #-}
{-
Copyright (C) 2006-2012 John MacFarlane
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 34962b553..df0a8294d 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2006-2010 John MacFarlane
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 9191f6908..8ccd1e227 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -290,13 +290,13 @@ rawHtmlBlock :: Parser [Char] ParserState Block
rawHtmlBlock = try $ do
(_,b) <- htmlTag isBlockTag
optional blanklines
- return $ RawBlock "html" b
+ return $ RawBlock (Format "html") b
-- | Raw block of LaTeX content
rawLaTeXBlock' :: Parser [Char] ParserState Block
rawLaTeXBlock' = do
guardEnabled Ext_raw_tex
- RawBlock "latex" <$> (rawLaTeXBlock <* spaces)
+ RawBlock (Format "latex") <$> (rawLaTeXBlock <* spaces)
-- | In textile, paragraphs are separated by blank lines.
@@ -487,7 +487,7 @@ endline = try $ do
return LineBreak
rawHtmlInline :: Parser [Char] ParserState Inline
-rawHtmlInline = RawInline "html" . snd <$> htmlTag isInlineTag
+rawHtmlInline = RawInline (Format "html") . snd <$> htmlTag isInlineTag
-- | Raw LaTeX Inline
rawLaTeXInline' :: Parser [Char] ParserState Inline
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 00cea27e5..68b525742 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -132,7 +132,9 @@ blockToAsciiDoc opts (Para inlines) = do
then text "\\"
else empty
return $ esc <> contents <> blankline
-blockToAsciiDoc _ (RawBlock _ _) = return empty
+blockToAsciiDoc _ (RawBlock f s)
+ | f == "asciidoc" = return $ text s
+ | otherwise = return empty
blockToAsciiDoc _ HorizontalRule =
return $ blankline <> text "'''''" <> blankline
blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
@@ -347,7 +349,9 @@ inlineToAsciiDoc _ (Math InlineMath str) =
return $ "latexmath:[$" <> text str <> "$]"
inlineToAsciiDoc _ (Math DisplayMath str) =
return $ "latexmath:[\\[" <> text str <> "\\]]"
-inlineToAsciiDoc _ (RawInline _ _) = return empty
+inlineToAsciiDoc _ (RawInline f s)
+ | f == "asciidoc" = return $ text s
+ | otherwise = return empty
inlineToAsciiDoc _ (LineBreak) = return $ " +" <> cr
inlineToAsciiDoc _ Space = return space
inlineToAsciiDoc opts (Cite _ lst) = inlineListToAsciiDoc opts lst
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index c250a240e..0234e1e35 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -33,6 +33,7 @@ module Text.Pandoc.Writers.Custom ( writeCustom ) where
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Data.List ( intersperse )
+import Data.Char ( toLower )
import Scripting.Lua (LuaState, StackValue, callfunc)
import qualified Scripting.Lua as Lua
import Text.Pandoc.UTF8 (fromString, toString)
@@ -78,6 +79,11 @@ instance StackValue a => StackValue [a] where
return (Just lst)
valuetype _ = Lua.TTABLE
+instance StackValue Format where
+ push lua (Format f) = Lua.push lua (map toLower f)
+ peek l n = fmap Format `fmap` Lua.peek l n
+ valuetype _ = Lua.TSTRING
+
instance (StackValue a, StackValue b) => StackValue (M.Map a b) where
push lua m = do
let xs = M.toList m
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 2f415f3ee..3d150d19b 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2006-2010 John MacFarlane
@@ -199,10 +200,10 @@ blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) =
in inTags True "orderedlist" attribs items
blockToDocbook opts (DefinitionList lst) =
inTagsIndented "variablelist" $ deflistItemsToDocbook opts lst
-blockToDocbook _ (RawBlock "docbook" str) = text str -- raw XML block
--- we allow html for compatibility with earlier versions of pandoc
-blockToDocbook _ (RawBlock "html" str) = text str -- raw XML block
-blockToDocbook _ (RawBlock _ _) = empty
+blockToDocbook _ (RawBlock f str)
+ | f == "docbook" = text str -- raw XML block
+ | f == "html" = text str -- allow html for backwards compatibility
+ | otherwise = empty
blockToDocbook _ HorizontalRule = empty -- not semantic
blockToDocbook opts (Table caption aligns widths headers rows) =
let captionDoc = if null caption
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index d93254971..2483e243f 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -460,8 +460,8 @@ blockToOpenXML opts (Para lst) = do
contents <- inlinesToOpenXML opts lst
return [mknode "w:p" [] (paraProps ++ contents)]
blockToOpenXML _ (RawBlock format str)
- | format == "openxml" = return [ x | Elem x <- parseXML str ]
- | otherwise = return []
+ | format == Format "openxml" = return [ x | Elem x <- parseXML str ]
+ | otherwise = return []
blockToOpenXML opts (BlockQuote blocks) =
withParaProp (pStyle "BlockQuote") $ blocksToOpenXML opts blocks
blockToOpenXML opts (CodeBlock attrs str) =
@@ -653,8 +653,8 @@ inlineToOpenXML opts (Strikeout lst) =
$ inlinesToOpenXML opts lst
inlineToOpenXML _ LineBreak = return [br]
inlineToOpenXML _ (RawInline f str)
- | f == "openxml" = return [ x | Elem x <- parseXML str ]
- | otherwise = return []
+ | f == Format "openxml" = return [ x | Elem x <- parseXML str ]
+ | otherwise = return []
inlineToOpenXML opts (Quoted quoteType lst) =
inlinesToOpenXML opts $ [Str open] ++ lst ++ [Str close]
where (open, close) = case quoteType of
@@ -688,7 +688,7 @@ inlineToOpenXML opts (Note bs) = do
let notemarker = mknode "w:r" []
[ mknode "w:rPr" [] (rStyle "FootnoteRef")
, mknode "w:footnoteRef" [] () ]
- let notemarkerXml = RawInline "openxml" $ ppElement notemarker
+ let notemarkerXml = RawInline (Format "openxml") $ ppElement notemarker
let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : ils) : xs
insertNoteRef (Para ils : xs) = Para (notemarkerXml : ils) : xs
insertNoteRef xs = Para [notemarkerXml] : xs
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index fb756f196..ab14ff8a0 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -103,7 +103,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
Just img -> do
let coverImage = "cover-image" ++ takeExtension img
let cpContent = renderHtml $ writeHtml opts'
- (Pandoc meta [RawBlock "html" $ "\n

\n
"])
+ (Pandoc meta [RawBlock (Format "html") $ "\n

\n
"])
imgContent <- B.readFile img
return ( [mkEntry "cover.xhtml" cpContent]
, [mkEntry coverImage imgContent] )
@@ -422,7 +422,7 @@ transformInline opts sourceDir picsRef (Image lab (src,tit))
| isAbsoluteURI src = do
raw <- makeSelfContained Nothing
$ writeHtmlInline opts (Image lab (src,tit))
- return $ RawInline "html" raw
+ return $ RawInline (Format "html") raw
| otherwise = do
let src' = unEscapeString src
pics <- readIORef picsRef
@@ -438,7 +438,7 @@ transformInline opts sourceDir picsRef (Image lab (src,tit))
transformInline opts _ _ (x@(Math _ _))
| WebTeX _ <- writerHTMLMathMethod opts = do
raw <- makeSelfContained Nothing $ writeHtmlInline opts x
- return $ RawInline "html" raw
+ return $ RawInline (Format "html") raw
transformInline _ _ _ x = return x
writeHtmlInline :: WriterOptions -> Inline -> String
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 560c26c76..25079574e 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -410,8 +410,9 @@ blockToHtml opts (Para lst) = do
blockToHtml opts (Div attr bs) = do
contents <- blockListToHtml opts bs
return $ addAttrs opts attr $ H.div $ nl opts >> contents >> nl opts
-blockToHtml _ (RawBlock "html" str) = return $ preEscapedString str
-blockToHtml _ (RawBlock _ _) = return mempty
+blockToHtml _ (RawBlock f str)
+ | f == Format "html" = return $ preEscapedString str
+ | otherwise = return mempty
blockToHtml opts (HorizontalRule) = return $ if writerHtml5 opts then H5.hr else H.hr
blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
let tolhs = isEnabled Ext_literate_haskell opts &&
@@ -678,12 +679,14 @@ inlineToHtml opts inline =
return $ case t of
InlineMath -> m
DisplayMath -> brtag >> m >> brtag )
- (RawInline "latex" str) -> case writerHTMLMathMethod opts of
+ (RawInline f str)
+ | f == Format "latex" ->
+ case writerHTMLMathMethod opts of
LaTeXMathML _ -> do modify (\st -> st {stMath = True})
return $ toHtml str
_ -> return mempty
- (RawInline "html" str) -> return $ preEscapedString str
- (RawInline _ _) -> return mempty
+ | f == Format "html" -> return $ preEscapedString str
+ | otherwise -> return mempty
(Link [Str str] (s,_)) | "mailto:" `isPrefixOf` s &&
s == escapeURI ("mailto" ++ str) ->
-- autolink
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 37de03e0f..d09ccc3b8 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -356,8 +356,10 @@ blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
Nothing -> rawCodeBlock
Just h -> modify (\st -> st{ stHighlighting = True }) >>
return (flush $ text h)
-blockToLaTeX (RawBlock "latex" x) = return $ text x
-blockToLaTeX (RawBlock _ _) = return empty
+blockToLaTeX (RawBlock f x)
+ | f == Format "latex" || f == Format "tex"
+ = return $ text x
+ | otherwise = return empty
blockToLaTeX (BulletList []) = return empty -- otherwise latex error
blockToLaTeX (BulletList lst) = do
incremental <- gets stIncremental
@@ -630,9 +632,10 @@ inlineToLaTeX (Math InlineMath str) =
return $ char '$' <> text str <> char '$'
inlineToLaTeX (Math DisplayMath str) =
return $ "\\[" <> text str <> "\\]"
-inlineToLaTeX (RawInline "latex" str) = return $ text str
-inlineToLaTeX (RawInline "tex" str) = return $ text str
-inlineToLaTeX (RawInline _ _) = return empty
+inlineToLaTeX (RawInline f str)
+ | f == Format "latex" || f == Format "tex"
+ = return $ text str
+ | otherwise = return empty
inlineToLaTeX (LineBreak) = return "\\\\"
inlineToLaTeX Space = return space
inlineToLaTeX (Link txt ('#':ident, _)) = do
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index ed66c7c2b..642a002d6 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -167,8 +167,9 @@ blockToMan opts (Para inlines) = do
contents <- liftM vcat $ mapM (inlineListToMan opts) $
splitSentences inlines
return $ text ".PP" $$ contents
-blockToMan _ (RawBlock "man" str) = return $ text str
-blockToMan _ (RawBlock _ _) = return empty
+blockToMan _ (RawBlock f str)
+ | f == Format "man" = return $ text str
+ | otherwise = return empty
blockToMan _ HorizontalRule = return $ text ".PP" $$ text " * * * * *"
blockToMan opts (Header level _ inlines) = do
contents <- inlineListToMan opts inlines
@@ -333,8 +334,9 @@ inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str
inlineToMan opts (Math DisplayMath str) = do
contents <- inlineListToMan opts $ readTeXMath str
return $ cr <> text ".RS" $$ contents $$ text ".RE"
-inlineToMan _ (RawInline "man" str) = return $ text str
-inlineToMan _ (RawInline _ _) = return empty
+inlineToMan _ (RawInline f str)
+ | f == Format "man" = return $ text str
+ | otherwise = return empty
inlineToMan _ (LineBreak) = return $
cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr
inlineToMan _ Space = return space
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index fccf25753..4ffba1100 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -107,9 +107,10 @@ blockToMediaWiki opts (Para inlines) = do
then "" ++ contents ++ "
"
else contents ++ if null listLevel then "\n" else ""
-blockToMediaWiki _ (RawBlock "mediawiki" str) = return str
-blockToMediaWiki _ (RawBlock "html" str) = return str
-blockToMediaWiki _ (RawBlock _ _) = return ""
+blockToMediaWiki _ (RawBlock f str)
+ | f == Format "mediawiki" = return str
+ | f == Format "html" = return str
+ | otherwise = return ""
blockToMediaWiki _ HorizontalRule = return "\n-----\n"
@@ -374,9 +375,10 @@ inlineToMediaWiki _ (Str str) = return $ escapeString str
inlineToMediaWiki _ (Math _ str) = return $ ""
-- note: str should NOT be escaped
-inlineToMediaWiki _ (RawInline "mediawiki" str) = return str
-inlineToMediaWiki _ (RawInline "html" str) = return str
-inlineToMediaWiki _ (RawInline _ _) = return ""
+inlineToMediaWiki _ (RawInline f str)
+ | f == Format "mediawiki" = return str
+ | f == Format "html" = return str
+ | otherwise = return ""
inlineToMediaWiki _ (LineBreak) = return "
"
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index d76d0f6ad..05c576c20 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE PatternGuards, OverloadedStrings #-}
{-
Copyright (C) 2008-2010 Andrea Rossato
and John MacFarlane.
@@ -296,7 +296,9 @@ blockToOpenDocument o bs
| Table c a w h r <- bs = setFirstPara >> table c a w h r
| HorizontalRule <- bs = setFirstPara >> return (selfClosingTag "text:p"
[ ("text:style-name", "Horizontal_20_Line") ])
- | RawBlock _ _ <- bs = return empty
+ | RawBlock f s <- bs = if f == "opendocument"
+ then preformatted s
+ else return empty
| Null <- bs = return empty
| otherwise = return empty
where
@@ -374,9 +376,9 @@ inlineToOpenDocument o ils
| Code _ s <- ils = preformatted s
| Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s)
| Cite _ l <- ils = inlinesToOpenDocument o l
- | RawInline "opendocument" s <- ils = preformatted s
- | RawInline "html" s <- ils = preformatted s -- for backwards compat.
- | RawInline _ _ <- ils = return empty
+ | RawInline f s <- ils = if f == "opendocument" || f == "html"
+ then preformatted s
+ else return empty
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
| Image _ (s,t) <- ils = return $ mkImg s t
| Note l <- ils = mkNote l
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 4d8daa15b..5fbbb6afc 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -42,7 +42,7 @@ import Network.URI (isAbsoluteURI)
import Text.Pandoc.Pretty
import Control.Monad.State
import Control.Applicative ( (<$>) )
-import Data.Char (isSpace)
+import Data.Char (isSpace, toLower)
type Refs = [([Inline], Target)]
@@ -176,9 +176,11 @@ blockToRST (Para inlines)
| otherwise = do
contents <- inlineListToRST inlines
return $ contents <> blankline
-blockToRST (RawBlock f str) =
- return $ blankline <> ".. raw:: " <> text f $+$
- (nest 3 $ text str) $$ blankline
+blockToRST (RawBlock f str)
+ | f == "rst" = return $ text str
+ | otherwise = return $ blankline <> ".. raw:: " <>
+ text (map toLower $ unFormat f) $+$
+ (nest 3 $ text str) $$ blankline
blockToRST HorizontalRule =
return $ blankline $$ "--------------" $$ blankline
blockToRST (Header level _ inlines) = do
@@ -374,8 +376,9 @@ inlineToRST (Math t str) = do
then blankline $$ ".. math::" $$
blankline $$ nest 3 (text str) $$ blankline
else blankline $$ (".. math:: " <> text str) $$ blankline
-inlineToRST (RawInline "rst" x) = return $ text x
-inlineToRST (RawInline _ _) = return empty
+inlineToRST (RawInline f x)
+ | f == "rst" = return $ text x
+ | otherwise = return empty
inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para)
inlineToRST Space = return space
-- autolink
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 7e5d33c50..6d2b1229d 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -62,7 +62,7 @@ rtfEmbedImage x@(Image _ (src,_)) = do
let raw = "{\\pict" ++ filetype ++ " " ++ concat bytes ++ "}"
return $ if B.null imgdata
then x
- else RawInline "rtf" raw
+ else RawInline (Format "rtf") raw
else return x
rtfEmbedImage x = return x
@@ -218,8 +218,9 @@ blockToRTF indent alignment (BlockQuote lst) =
concatMap (blockToRTF (indent + indentIncrement) alignment) lst
blockToRTF indent _ (CodeBlock _ str) =
rtfPar indent 0 AlignLeft ("\\f1 " ++ (codeStringToRTF str))
-blockToRTF _ _ (RawBlock "rtf" str) = str
-blockToRTF _ _ (RawBlock _ _) = ""
+blockToRTF _ _ (RawBlock f str)
+ | f == Format "rtf" = str
+ | otherwise = ""
blockToRTF indent alignment (BulletList lst) = spaceAtEnd $
concatMap (listItemToRTF alignment indent (bulletMarker indent)) lst
blockToRTF indent alignment (OrderedList attribs lst) = spaceAtEnd $ concat $
@@ -325,8 +326,9 @@ inlineToRTF (Code _ str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}"
inlineToRTF (Str str) = stringToRTF str
inlineToRTF (Math _ str) = inlineListToRTF $ readTeXMath str
inlineToRTF (Cite _ lst) = inlineListToRTF lst
-inlineToRTF (RawInline "rtf" str) = str
-inlineToRTF (RawInline _ _) = ""
+inlineToRTF (RawInline f str)
+ | f == Format "rtf" = str
+ | otherwise = ""
inlineToRTF (LineBreak) = "\\line "
inlineToRTF Space = " "
inlineToRTF (Link text (src, _)) =
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index f8b460001..b1fd3d6af 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2008-2010 John MacFarlane and Peter Wang
@@ -152,10 +153,11 @@ blockToTexinfo (CodeBlock _ str) = do
flush (text str) $$
text "@end verbatim" <> blankline
-blockToTexinfo (RawBlock "texinfo" str) = return $ text str
-blockToTexinfo (RawBlock "latex" str) =
- return $ text "@tex" $$ text str $$ text "@end tex"
-blockToTexinfo (RawBlock _ _) = return empty
+blockToTexinfo (RawBlock f str)
+ | f == "texinfo" = return $ text str
+ | f == "latex" || f == "tex" =
+ return $ text "@tex" $$ text str $$ text "@end tex"
+ | otherwise = return empty
blockToTexinfo (BulletList lst) = do
items <- mapM listItemToTexinfo lst
@@ -418,10 +420,11 @@ inlineToTexinfo (Cite _ lst) =
inlineListToTexinfo lst
inlineToTexinfo (Str str) = return $ text (stringToTexinfo str)
inlineToTexinfo (Math _ str) = return $ inCmd "math" $ text str
-inlineToTexinfo (RawInline f str) | f == "latex" || f == "tex" =
- return $ text "@tex" $$ text str $$ text "@end tex"
-inlineToTexinfo (RawInline "texinfo" str) = return $ text str
-inlineToTexinfo (RawInline _ _) = return empty
+inlineToTexinfo (RawInline f str)
+ | f == "latex" || f == "tex" =
+ return $ text "@tex" $$ text str $$ text "@end tex"
+ | f == "texinfo" = return $ text str
+ | otherwise = return empty
inlineToTexinfo (LineBreak) = return $ text "@*"
inlineToTexinfo Space = return $ char ' '
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 3fb554dca..27e8b60ec 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -121,10 +121,9 @@ blockToTextile opts (Para inlines) = do
then "" ++ contents ++ "
"
else contents ++ if null listLevel then "\n" else ""
-blockToTextile _ (RawBlock f str) =
- if f == "html" || f == "textile"
- then return str
- else return ""
+blockToTextile _ (RawBlock f str)
+ | f == Format "html" || f == Format "textile" = return str
+ | otherwise = return ""
blockToTextile _ HorizontalRule = return "
\n"
@@ -401,10 +400,9 @@ inlineToTextile _ (Str str) = return $ escapeStringForTextile str
inlineToTextile _ (Math _ str) =
return $ "" ++ escapeStringForXML str ++ ""
-inlineToTextile _ (RawInline f str) =
- if f == "html" || f == "textile"
- then return str
- else return ""
+inlineToTextile _ (RawInline f str)
+ | f == Format "html" || f == Format "textile" = return str
+ | otherwise = return ""
inlineToTextile _ (LineBreak) = return "\n"
diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs
index 5939d088d..31c0cb46a 100644
--- a/tests/Tests/Arbitrary.hs
+++ b/tests/Tests/Arbitrary.hs
@@ -41,8 +41,8 @@ arbInline :: Int -> Gen Inline
arbInline n = frequency $ [ (60, liftM Str realString)
, (60, return Space)
, (10, liftM2 Code arbAttr realString)
- , (5, elements [ RawInline "html" ""
- , RawInline "latex" "\\my{command}" ])
+ , (5, elements [ RawInline (Format "html") ""
+ , RawInline (Format "latex") "\\my{command}" ])
] ++ [ x | x <- nesters, n > 1]
where nesters = [ (10, liftM Emph $ arbInlines (n-1))
, (10, liftM Strong $ arbInlines (n-1))
@@ -74,9 +74,9 @@ arbBlock :: Int -> Gen Block
arbBlock n = frequency $ [ (10, liftM Plain $ arbInlines (n-1))
, (15, liftM Para $ arbInlines (n-1))
, (5, liftM2 CodeBlock arbAttr realString)
- , (2, elements [ RawBlock "html"
+ , (2, elements [ RawBlock (Format "html")
"\n*&*\n
"
- , RawBlock "latex"
+ , RawBlock (Format "latex")
"\\begin[opt]{env}\nhi\n{\\end{env}"
])
, (5, do x1 <- choose (1 :: Int, 6)
--
cgit v1.2.3
From 9152fa1a95346e26bc290b3f5018b2eeb5d4e077 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sat, 10 Aug 2013 18:13:38 -0700
Subject: Use query instead of queryWith.
---
src/Text/Pandoc/Biblio.hs | 5 +++--
src/Text/Pandoc/Shared.hs | 29 +++++++++++++++++++++++++++--
src/Text/Pandoc/Writers/ConTeXt.hs | 4 ++--
src/Text/Pandoc/Writers/LaTeX.hs | 7 ++++---
4 files changed, 36 insertions(+), 9 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs
index 755c779ea..206b38530 100644
--- a/src/Text/Pandoc/Biblio.hs
+++ b/src/Text/Pandoc/Biblio.hs
@@ -36,6 +36,7 @@ import Text.CSL hiding ( Cite(..), Citation(..), endWithPunct )
import qualified Text.CSL as CSL ( Cite(..) )
import Text.Pandoc.Definition
import Text.Pandoc.Generic
+import Text.Pandoc.Walk
import Text.Pandoc.Shared (stringify)
import Text.Parsec hiding (State)
import Control.Monad
@@ -48,7 +49,7 @@ processBiblio Nothing _ p = p
processBiblio _ [] p = p
processBiblio (Just style) r p =
let p' = evalState (bottomUpM setHash p) 1
- grps = queryWith getCitation p'
+ grps = query getCitation p'
result = citeproc procOpts style r (setNearNote style $
map (map toCslCite) grps)
cits_map = M.fromList $ zip grps (citations result)
@@ -121,7 +122,7 @@ isTextualCitation (c:_) = citationMode c == AuthorInText
isTextualCitation _ = False
-- | Retrieve all citations from a 'Pandoc' docuument. To be used with
--- 'queryWith'.
+-- 'query'.
getCitation :: Inline -> [[Citation]]
getCitation i | Cite t _ <- i = [t]
| otherwise = []
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 09874299d..2b692dc3c 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, CPP #-}
+{-# LANGUAGE DeriveDataTypeable, CPP, MultiParamTypeClasses #-}
{-
Copyright (C) 2006-2013 John MacFarlane
@@ -79,6 +79,7 @@ module Text.Pandoc.Shared (
) where
import Text.Pandoc.Definition
+import Text.Pandoc.Walk
import Text.Pandoc.Generic
import Text.Pandoc.Builder (Blocks, ToMetaValue(..))
import qualified Text.Pandoc.Builder as B
@@ -105,6 +106,7 @@ import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..),
renderOptions)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as B8
+import Text.Pandoc.Compat.Monoid
#ifdef EMBED_DATA_FILES
import Text.Pandoc.Data (dataFiles)
@@ -383,7 +385,7 @@ consolidateInlines [] = []
-- | Convert list of inlines to a string with formatting removed.
stringify :: [Inline] -> String
-stringify = queryWith go
+stringify = query go
where go :: Inline -> [Char]
go Space = " "
go (Str x) = x
@@ -433,6 +435,29 @@ data Element = Blk Block
-- lvl num attributes label contents
deriving (Eq, Read, Show, Typeable, Data)
+instance Walkable Inline Element where
+ walk f (Blk x) = Blk (walk f x)
+ walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts)
+ walkM f (Blk x) = Blk `fmap` walkM f x
+ walkM f (Sec lev nums attr ils elts) = do
+ ils' <- walkM f ils
+ elts' <- walkM f elts
+ return $ Sec lev nums attr ils' elts'
+ query f (Blk x) = query f x
+ query f (Sec _ _ _ ils elts) = query f ils <> query f elts
+
+instance Walkable Block Element where
+ walk f (Blk x) = Blk (walk f x)
+ walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts)
+ walkM f (Blk x) = Blk `fmap` walkM f x
+ walkM f (Sec lev nums attr ils elts) = do
+ ils' <- walkM f ils
+ elts' <- walkM f elts
+ return $ Sec lev nums attr ils' elts'
+ query f (Blk x) = query f x
+ query f (Sec _ _ _ ils elts) = query f ils <> query f elts
+
+
-- | Convert Pandoc inline list to plain text identifier. HTML
-- identifiers must start with a letter, and may contain only
-- letters, digits, and the characters _-.
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 40dc1deb5..0379f8b0a 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -33,7 +33,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options
-import Text.Pandoc.Generic (queryWith)
+import Text.Pandoc.Walk (query)
import Text.Printf ( printf )
import Data.List ( intercalate, isPrefixOf )
import Control.Monad.State
@@ -326,7 +326,7 @@ inlineToConTeXt (Note contents) = do
contents' <- blockListToConTeXt contents
let codeBlock x@(CodeBlock _ _) = [x]
codeBlock _ = []
- let codeBlocks = queryWith codeBlock contents
+ let codeBlocks = query codeBlock contents
return $ if null codeBlocks
then text "\\footnote{" <> nest 2 contents' <> char '}'
else text "\\startbuffer " <> nest 2 contents' <>
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index d09ccc3b8..860ca8349 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -30,6 +30,7 @@ Conversion of 'Pandoc' format into LaTeX.
-}
module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where
import Text.Pandoc.Definition
+import Text.Pandoc.Walk
import Text.Pandoc.Generic
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
@@ -86,7 +87,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
-- see if there are internal links
let isInternalLink (Link _ ('#':xs,_)) = [xs]
isInternalLink _ = []
- modify $ \s -> s{ stInternalLinks = queryWith isInternalLink blocks }
+ modify $ \s -> s{ stInternalLinks = query isInternalLink blocks }
let template = writerTemplate options
-- set stBook depending on documentclass
let bookClasses = ["memoir","book","report","scrreprt","scrbook"]
@@ -248,9 +249,9 @@ elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts)
let hasCode (Code _ _) = [True]
hasCode _ = []
opts <- gets stOptions
- let fragile = not $ null $ queryWith hasCodeBlock elts ++
+ let fragile = not $ null $ query hasCodeBlock elts ++
if writerListings opts
- then queryWith hasCode elts
+ then query hasCode elts
else []
let allowframebreaks = "allowframebreaks" `elem` classes
let optionslist = ["fragile" | fragile] ++
--
cgit v1.2.3
From 02a125d0aa8becd258c99b27c5e30116f0cbacb4 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sat, 10 Aug 2013 18:45:00 -0700
Subject: Use walk, walkM in place of bottomUp, bottomUpM when possible.
They are significantly faster.
---
src/Text/Pandoc/PDF.hs | 4 ++--
src/Text/Pandoc/Readers/LaTeX.hs | 4 ++--
src/Text/Pandoc/Readers/MediaWiki.hs | 4 ++--
src/Text/Pandoc/Shared.hs | 2 +-
src/Text/Pandoc/Writers/Docx.hs | 11 ++++++-----
src/Text/Pandoc/Writers/EPUB.hs | 6 +++---
src/Text/Pandoc/Writers/FB2.hs | 8 ++++++--
src/Text/Pandoc/Writers/LaTeX.hs | 3 +--
src/Text/Pandoc/Writers/Markdown.hs | 8 ++++----
src/Text/Pandoc/Writers/ODT.hs | 4 ++--
src/Text/Pandoc/Writers/RTF.hs | 4 ++--
11 files changed, 31 insertions(+), 27 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index b030e2ca7..ce20ac1b4 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -44,7 +44,7 @@ import Data.List (isInfixOf)
import qualified Data.ByteString.Base64 as B64
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Definition
-import Text.Pandoc.Generic (bottomUpM)
+import Text.Pandoc.Walk (walkM)
import Text.Pandoc.Shared (fetchItem, warn)
import Text.Pandoc.Options (WriterOptions(..))
import Text.Pandoc.MIME (extensionFromMimeType)
@@ -73,7 +73,7 @@ handleImages :: String -- ^ source directory/base URL
-> FilePath -- ^ temp dir to store images
-> Pandoc -- ^ document
-> IO Pandoc
-handleImages baseURL tmpdir = bottomUpM (handleImage' baseURL tmpdir)
+handleImages baseURL tmpdir = walkM (handleImage' baseURL tmpdir)
handleImage' :: String
-> FilePath
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index eb0baedda..71e1e0ac2 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -35,7 +35,7 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,
) where
import Text.Pandoc.Definition
-import Text.Pandoc.Generic
+import Text.Pandoc.Walk
import Text.Pandoc.Shared
import Text.Pandoc.Options
import Text.Pandoc.Biblio (processBiblio)
@@ -815,7 +815,7 @@ keyvals :: LP [(String, String)]
keyvals = try $ char '[' *> manyTill keyval (char ']')
alltt :: String -> LP Blocks
-alltt t = bottomUp strToCode <$> parseFromString blocks
+alltt t = walk strToCode <$> parseFromString blocks
(substitute " " "\\ " $ substitute "%" "\\%" $
concat $ intersperse "\\\\\n" $ lines t)
where strToCode (Str s) = Code nullAttr s
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 56049e035..8f1ff2776 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -42,7 +42,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isCommentTag )
import Text.Pandoc.XML ( fromEntities )
import Text.Pandoc.Parsing hiding ( nested )
-import Text.Pandoc.Generic ( bottomUp )
+import Text.Pandoc.Walk ( walk )
import Text.Pandoc.Shared ( stripTrailingNewlines, safeRead )
import Data.Monoid (mconcat, mempty)
import Control.Applicative ((<$>), (<*), (*>), (<$))
@@ -342,7 +342,7 @@ preformatted = try $ do
spacesStr _ = False
if F.all spacesStr contents
then return mempty
- else return $ B.para $ bottomUp strToCode contents
+ else return $ B.para $ walk strToCode contents
header :: MWParser Blocks
header = try $ do
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 2b692dc3c..6fd78b188 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -518,7 +518,7 @@ isHeaderBlock _ = False
-- | Shift header levels up or down.
headerShift :: Int -> Pandoc -> Pandoc
-headerShift n = bottomUp shift
+headerShift n = walk shift
where shift :: Block -> Block
shift (Header level attr inner) = Header (level + n) attr inner
shift x = x
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 2483e243f..aa618b2cc 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -45,6 +45,7 @@ import Text.Pandoc.Shared hiding (Element)
import Text.Pandoc.Options
import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Highlighting ( highlight )
+import Text.Pandoc.Walk
import Text.Highlighting.Kate.Types ()
import Text.XML.Light
import Text.TeXMath
@@ -108,7 +109,7 @@ writeDocx :: WriterOptions -- ^ Writer options
-> IO BL.ByteString
writeDocx opts doc@(Pandoc meta _) = do
let datadir = writerUserDataDir opts
- let doc' = bottomUp (concatMap fixDisplayMath) doc
+ let doc' = walk fixDisplayMath doc
refArchive <- liftM (toArchive . toLazy) $
case writerReferenceDocx opts of
Just f -> B.readFile f
@@ -810,17 +811,17 @@ stripLeadingTrailingSpace = go . reverse . go . reverse
where go (Space:xs) = xs
go xs = xs
-fixDisplayMath :: Block -> [Block]
+fixDisplayMath :: Block -> Block
fixDisplayMath (Plain lst)
| any isDisplayMath lst && not (all isDisplayMath lst) =
-- chop into several paragraphs so each displaymath is its own
- map (Plain . stripLeadingTrailingSpace) $
+ Div ("",["math"],[]) $ map (Plain . stripLeadingTrailingSpace) $
groupBy (\x y -> (isDisplayMath x && isDisplayMath y) ||
not (isDisplayMath x || isDisplayMath y)) lst
fixDisplayMath (Para lst)
| any isDisplayMath lst && not (all isDisplayMath lst) =
-- chop into several paragraphs so each displaymath is its own
- map (Para . stripLeadingTrailingSpace) $
+ Div ("",["math"],[]) $ map (Para . stripLeadingTrailingSpace) $
groupBy (\x y -> (isDisplayMath x && isDisplayMath y) ||
not (isDisplayMath x || isDisplayMath y)) lst
-fixDisplayMath x = [x]
+fixDisplayMath x = x
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index ab14ff8a0..fa2b45036 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -48,7 +48,7 @@ import qualified Text.Pandoc.Shared as Shared
import Text.Pandoc.Builder (fromList, setMeta)
import Text.Pandoc.Options
import Text.Pandoc.Definition
-import Text.Pandoc.Generic
+import Text.Pandoc.Walk
import Control.Monad.State
import Text.XML.Light hiding (ppTopElement)
import Text.Pandoc.UUID
@@ -116,7 +116,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
-- handle pictures
picsRef <- newIORef []
- Pandoc _ blocks <- bottomUpM
+ Pandoc _ blocks <- walkM
(transformInline opts' sourceDir picsRef) doc
pics <- readIORef picsRef
let readPicEntry entries (oldsrc, newsrc) = do
@@ -520,7 +520,7 @@ correlateRefs chapterHeaderLevel bs =
-- Replace internal link references using the table produced
-- by correlateRefs.
replaceRefs :: [(String,String)] -> [Block] -> [Block]
-replaceRefs refTable = bottomUp replaceOneRef
+replaceRefs refTable = walk replaceOneRef
where replaceOneRef x@(Link lab ('#':xs,tit)) =
case lookup xs refTable of
Just url -> Link lab (url,tit)
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 2576b2dc2..adbe948be 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -45,7 +45,7 @@ import qualified Text.XML.Light.Cursor as XC
import Text.Pandoc.Definition
import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), def)
import Text.Pandoc.Shared (orderedListMarkers)
-import Text.Pandoc.Generic (bottomUp)
+import Text.Pandoc.Walk
-- | Data to be written at the end of the document:
-- (foot)notes, URLs, references, images.
@@ -423,6 +423,10 @@ indent = indentBlock
indentLines ins = let lns = split isLineBreak ins :: [[Inline]]
in intercalate [LineBreak] $ map ((Str spacer):) lns
+capitalize :: Inline -> Inline
+capitalize (Str xs) = Str $ map toUpper xs
+capitalize x = x
+
-- | Convert a Pandoc's Inline element to FictionBook XML representation.
toXml :: Inline -> FBM [Content]
toXml (Str s) = return [txt s]
@@ -432,7 +436,7 @@ toXml (Strong ss) = list `liftM` wrap "strong" ss
toXml (Strikeout ss) = list `liftM` wrap "strikethrough" ss
toXml (Superscript ss) = list `liftM` wrap "sup" ss
toXml (Subscript ss) = list `liftM` wrap "sub" ss
-toXml (SmallCaps ss) = cMapM toXml $ bottomUp (map toUpper) ss
+toXml (SmallCaps ss) = cMapM toXml $ walk capitalize ss
toXml (Quoted SingleQuote ss) = do -- FIXME: should be language-specific
inner <- cMapM toXml ss
return $ [txt "‘"] ++ inner ++ [txt "’"]
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 860ca8349..7f9a99801 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -31,7 +31,6 @@ Conversion of 'Pandoc' format into LaTeX.
module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where
import Text.Pandoc.Definition
import Text.Pandoc.Walk
-import Text.Pandoc.Generic
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options
@@ -498,7 +497,7 @@ sectionHeader unnumbered ref level lst = do
txt <- inlineListToLaTeX lst
let noNote (Note _) = Str ""
noNote x = x
- let lstNoNotes = bottomUp noNote lst
+ let lstNoNotes = walk noNote lst
let star = if unnumbered then text "*" else empty
-- footnotes in sections don't work unless you specify an optional
-- argument: \section[mysec]{mysec\footnote{blah}}
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index d195d8445..3d0ed8702 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -32,7 +32,7 @@ Markdown:
-}
module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where
import Text.Pandoc.Definition
-import Text.Pandoc.Generic
+import Text.Pandoc.Walk
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
@@ -82,7 +82,7 @@ writePlain opts document =
where document' = plainify document
plainify :: Pandoc -> Pandoc
-plainify = bottomUp go
+plainify = walk go
where go :: Inline -> Inline
go (Emph xs) = SmallCaps xs
go (Strong xs) = SmallCaps xs
@@ -643,13 +643,13 @@ inlineToMarkdown opts (Strikeout lst) = do
then "~~" <> contents <> "~~"
else "" <> contents <> ""
inlineToMarkdown opts (Superscript lst) = do
- let lst' = bottomUp escapeSpaces lst
+ let lst' = walk escapeSpaces lst
contents <- inlineListToMarkdown opts lst'
return $ if isEnabled Ext_superscript opts
then "^" <> contents <> "^"
else "" <> contents <> ""
inlineToMarkdown opts (Subscript lst) = do
- let lst' = bottomUp escapeSpaces lst
+ let lst' = walk escapeSpaces lst
contents <- inlineListToMarkdown opts lst'
return $ if isEnabled Ext_subscript opts
then "~" <> contents <> "~"
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 589010bb9..fb94d9ffb 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -39,7 +39,7 @@ import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem, warn )
import Text.Pandoc.ImageSize ( imageSize, sizeInPoints )
import Text.Pandoc.MIME ( getMimeType )
import Text.Pandoc.Definition
-import Text.Pandoc.Generic
+import Text.Pandoc.Walk
import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument )
import Control.Monad (liftM)
import Text.Pandoc.XML
@@ -63,7 +63,7 @@ writeODT opts doc@(Pandoc meta _) = do
-- handle pictures
picEntriesRef <- newIORef ([] :: [Entry])
let sourceDir = writerSourceDirectory opts
- doc' <- bottomUpM (transformPic sourceDir picEntriesRef) doc
+ doc' <- walkM (transformPic sourceDir picEntriesRef) doc
let newContents = writeOpenDocument opts{writerWrapText = False} doc'
epochtime <- floor `fmap` getPOSIXTime
let contentEntry = toEntry "content.xml" epochtime $ fromStringLazy newContents
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 6d2b1229d..0e8ce2ece 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -34,7 +34,7 @@ import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Generic (bottomUpM)
+import Text.Pandoc.Walk
import Data.List ( isSuffixOf, intercalate )
import Data.Char ( ord, chr, isDigit, toLower )
import System.FilePath ( takeExtension )
@@ -70,7 +70,7 @@ rtfEmbedImage x = return x
-- images embedded as encoded binary data.
writeRTFWithEmbeddedImages :: WriterOptions -> Pandoc -> IO String
writeRTFWithEmbeddedImages options doc =
- writeRTF options `fmap` bottomUpM rtfEmbedImage doc
+ writeRTF options `fmap` walkM rtfEmbedImage doc
-- | Convert Pandoc to a string in rich text format.
writeRTF :: WriterOptions -> Pandoc -> String
--
cgit v1.2.3
From e279175ea517e2df65fe5d716bc02e383b04fc36 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 11 Aug 2013 15:58:09 -0700
Subject: Options: Changed `writerSourceDir` to `writerSourceURL` (now a
Maybe).
Previously we used to store the directory of the first input file,
even if it was local, and used this as a base directory for
finding images in ODT, EPUB, Docx, and PDF.
This has been confusing to many users. It seems better to look for
images relative to the current working directory, even if the first
file argument is in another directory.
writerSourceURL is set to 'Just url' when the first command-line
argument is an absolute URL. (So, relative links will be resolved
in relation to the first page.) Otherwise, 'Nothing'.
The ODT, EPUB, Docx, and PDF writers have been modified accordingly.
Note that this change may break some existing workflows. If you
have been assuming that relative links will be interpreted relative
to the directory of the first file argument, you'll need to
make that the current directory before running pandoc.
Closes #942.
---
pandoc.hs | 12 +++++++-----
src/Text/Pandoc/Options.hs | 4 ++--
src/Text/Pandoc/PDF.hs | 6 +++---
src/Text/Pandoc/Shared.hs | 20 ++++++++++----------
src/Text/Pandoc/Writers/Docx.hs | 3 +--
src/Text/Pandoc/Writers/EPUB.hs | 21 +++++++--------------
src/Text/Pandoc/Writers/ODT.hs | 9 ++++-----
7 files changed, 34 insertions(+), 41 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/pandoc.hs b/pandoc.hs
index fdf0b35b7..81672e16c 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1034,13 +1034,15 @@ main = do
return $ Just csl { CSL.styleAbbrevs = abbrevs }
else return Nothing
- let sourceDir = case sources of
- [] -> "."
+ let sourceURL = case sources of
+ [] -> Nothing
(x:_) -> case parseURI x of
Just u
| uriScheme u `elem` ["http:","https:"] ->
- show u{ uriPath = "", uriQuery = "", uriFragment = "" }
- _ -> takeDirectory x
+ Just $ show u{ uriPath = "",
+ uriQuery = "",
+ uriFragment = "" }
+ _ -> Nothing
let readerOpts = def{ readerSmart = smart || (texLigatures &&
(laTeXOutput || "context" `isPrefixOf` writerName'))
@@ -1074,7 +1076,7 @@ main = do
writerColumns = columns,
writerEmailObfuscation = obfuscationMethod,
writerIdentifierPrefix = idPrefix,
- writerSourceDirectory = sourceDir,
+ writerSourceURL = sourceURL,
writerUserDataDir = datadir,
writerHtml5 = html5,
writerHtmlQTags = htmlQTags,
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 61a85cf6e..c7c37d6b8 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -286,7 +286,7 @@ data WriterOptions = WriterOptions
, writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails
, writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML
-- and for footnote marks in markdown
- , writerSourceDirectory :: FilePath -- ^ Directory path of 1st source file
+ , writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file
, writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory
, writerCiteMethod :: CiteMethod -- ^ How to print cites
, writerBiblioFiles :: [FilePath] -- ^ Biblio files to use for citations
@@ -329,7 +329,7 @@ instance Default WriterOptions where
, writerColumns = 72
, writerEmailObfuscation = JavascriptObfuscation
, writerIdentifierPrefix = ""
- , writerSourceDirectory = "."
+ , writerSourceURL = Nothing
, writerUserDataDir = Nothing
, writerCiteMethod = Citeproc
, writerBiblioFiles = []
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index ce20ac1b4..ae611bc37 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -65,17 +65,17 @@ makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex)
-> Pandoc -- ^ document
-> IO (Either ByteString ByteString)
makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do
- doc' <- handleImages (writerSourceDirectory opts) tmpdir doc
+ doc' <- handleImages (writerSourceURL opts) tmpdir doc
let source = writer opts doc'
tex2pdf' tmpdir program source
-handleImages :: String -- ^ source directory/base URL
+handleImages :: Maybe String -- ^ source base URL
-> FilePath -- ^ temp dir to store images
-> Pandoc -- ^ document
-> IO Pandoc
handleImages baseURL tmpdir = walkM (handleImage' baseURL tmpdir)
-handleImage' :: String
+handleImage' :: Maybe String
-> FilePath
-> Inline
-> IO Inline
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 6fd78b188..d670a35bc 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -612,18 +612,18 @@ readDataFileUTF8 userDir fname =
-- | Fetch an image or other item from the local filesystem or the net.
-- Returns raw content and maybe mime type.
-fetchItem :: String -> String
+fetchItem :: Maybe String -> String
-> IO (Either E.SomeException (BS.ByteString, Maybe String))
-fetchItem sourceDir s =
- case s of
- _ | isAbsoluteURI s -> openURL s
- | isAbsoluteURI sourceDir -> openURL $ sourceDir ++ "/" ++ s
- | otherwise -> E.try $ do
+fetchItem sourceURL s
+ | isAbsoluteURI s = openURL s
+ | otherwise = case sourceURL of
+ Just u -> openURL (u ++ "/" ++ s)
+ Nothing -> E.try readLocalFile
+ where readLocalFile = do
let mime = case takeExtension s of
- ".gz" -> getMimeType $ dropExtension s
- x -> getMimeType x
- let f = sourceDir > s
- cont <- BS.readFile f
+ ".gz" -> getMimeType $ dropExtension s
+ x -> getMimeType x
+ cont <- BS.readFile s
return (cont, mime)
-- | Read from a URL and return raw data and maybe mime type.
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index aa618b2cc..c8673ae48 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -728,8 +728,7 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
case M.lookup src imgs of
Just (_,_,_,elt,_) -> return [elt]
Nothing -> do
- let sourceDir = writerSourceDirectory opts
- res <- liftIO $ fetchItem sourceDir src
+ res <- liftIO $ fetchItem (writerSourceURL opts) src
case res of
Left (_ :: E.SomeException) -> do
liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..."
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index fa2b45036..ac0e7610c 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -55,7 +55,7 @@ import Text.Pandoc.UUID
import Text.Pandoc.Writers.HTML
import Text.Pandoc.Writers.Markdown ( writePlain )
import Data.Char ( toLower )
-import Network.URI ( isAbsoluteURI, unEscapeString )
+import Network.URI ( unEscapeString )
import Text.Pandoc.MIME (getMimeType)
#if MIN_VERSION_base(4,6,0)
#else
@@ -93,7 +93,6 @@ writeEPUB opts doc@(Pandoc meta _) = do
then MathML Nothing
else writerHTMLMathMethod opts
, writerWrapText = False }
- let sourceDir = writerSourceDirectory opts'
let mbCoverImage = lookup "epub-cover-image" vars
-- cover page
@@ -117,10 +116,10 @@ writeEPUB opts doc@(Pandoc meta _) = do
-- handle pictures
picsRef <- newIORef []
Pandoc _ blocks <- walkM
- (transformInline opts' sourceDir picsRef) doc
+ (transformInline opts' picsRef) doc
pics <- readIORef picsRef
let readPicEntry entries (oldsrc, newsrc) = do
- res <- fetchItem sourceDir oldsrc
+ res <- fetchItem (writerSourceURL opts') oldsrc
case res of
Left _ -> do
warn $ "Could not find image `" ++ oldsrc ++ "', skipping..."
@@ -414,19 +413,13 @@ showDateTimeISO8601 :: UTCTime -> String
showDateTimeISO8601 = formatTime defaultTimeLocale "%FT%TZ"
transformInline :: WriterOptions
- -> FilePath
-> IORef [(FilePath, FilePath)] -- ^ (oldpath, newpath) images
-> Inline
-> IO Inline
-transformInline opts sourceDir picsRef (Image lab (src,tit))
- | isAbsoluteURI src = do
- raw <- makeSelfContained Nothing
- $ writeHtmlInline opts (Image lab (src,tit))
- return $ RawInline (Format "html") raw
- | otherwise = do
+transformInline opts picsRef (Image lab (src,tit)) = do
let src' = unEscapeString src
pics <- readIORef picsRef
- let oldsrc = sourceDir > src'
+ let oldsrc = maybe src' (> src) $ writerSourceURL opts
let ext = takeExtension src'
newsrc <- case lookup oldsrc pics of
Just n -> return n
@@ -435,11 +428,11 @@ transformInline opts sourceDir picsRef (Image lab (src,tit))
modifyIORef picsRef ( (oldsrc, new): )
return new
return $ Image lab (newsrc, tit)
-transformInline opts _ _ (x@(Math _ _))
+transformInline opts _ (x@(Math _ _))
| WebTeX _ <- writerHTMLMathMethod opts = do
raw <- makeSelfContained Nothing $ writeHtmlInline opts x
return $ RawInline (Format "html") raw
-transformInline _ _ _ x = return x
+transformInline _ _ x = return x
writeHtmlInline :: WriterOptions -> Inline -> String
writeHtmlInline opts z = trimr $
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index fb94d9ffb..751a323f5 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -62,8 +62,7 @@ writeODT opts doc@(Pandoc meta _) = do
readDataFile datadir "reference.odt"
-- handle pictures
picEntriesRef <- newIORef ([] :: [Entry])
- let sourceDir = writerSourceDirectory opts
- doc' <- walkM (transformPic sourceDir picEntriesRef) doc
+ doc' <- walkM (transformPic opts picEntriesRef) doc
let newContents = writeOpenDocument opts{writerWrapText = False} doc'
epochtime <- floor `fmap` getPOSIXTime
let contentEntry = toEntry "content.xml" epochtime $ fromStringLazy newContents
@@ -111,9 +110,9 @@ writeODT opts doc@(Pandoc meta _) = do
let archive'' = addEntryToArchive metaEntry archive'
return $ fromArchive archive''
-transformPic :: FilePath -> IORef [Entry] -> Inline -> IO Inline
-transformPic sourceDir entriesRef (Image lab (src,_)) = do
- res <- fetchItem sourceDir src
+transformPic :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline
+transformPic opts entriesRef (Image lab (src,_)) = do
+ res <- fetchItem (writerSourceURL opts) src
case res of
Left (_ :: E.SomeException) -> do
warn $ "Could not find image `" ++ src ++ "', skipping..."
--
cgit v1.2.3
From eb0c0b86ed518982eb5d3336e73ff5cb1d59d87c Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 11 Aug 2013 17:13:46 -0700
Subject: ODT/OpenDocument writer: Minor changes for ODF 1.2 conformance.
See #939. We leave the nonconforming contextual-spacing attribute,
which is provided by LibreOffice itself and seems to be supported.
---
data/reference.odt | Bin 7058 -> 10702 bytes
data/templates | 2 +-
src/Text/Pandoc/Writers/ODT.hs | 20 ++++++++++++++------
src/Text/Pandoc/Writers/OpenDocument.hs | 3 ++-
tests/writer.opendocument | 2 +-
5 files changed, 18 insertions(+), 9 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/data/reference.odt b/data/reference.odt
index 6307119d3..29c1777d7 100644
Binary files a/data/reference.odt and b/data/reference.odt differ
diff --git a/data/templates b/data/templates
index c27f59c01..0cb55f228 160000
--- a/data/templates
+++ b/data/templates
@@ -1 +1 @@
-Subproject commit c27f59c010b0468f01b710cdf3a3c04a450a03e7
+Subproject commit 0cb55f2289148b106ab78ce8f15efc8d0b8acda0
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 751a323f5..cc0a06243 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -65,26 +65,30 @@ writeODT opts doc@(Pandoc meta _) = do
doc' <- walkM (transformPic opts picEntriesRef) doc
let newContents = writeOpenDocument opts{writerWrapText = False} doc'
epochtime <- floor `fmap` getPOSIXTime
- let contentEntry = toEntry "content.xml" epochtime $ fromStringLazy newContents
+ let contentEntry = toEntry "content.xml" epochtime
+ $ fromStringLazy newContents
picEntries <- readIORef picEntriesRef
- let archive = foldr addEntryToArchive refArchive $ contentEntry : picEntries
+ let archive = foldr addEntryToArchive refArchive
+ $ contentEntry : picEntries
-- construct META-INF/manifest.xml based on archive
let toFileEntry fp = case getMimeType fp of
Nothing -> empty
Just m -> selfClosingTag "manifest:file-entry"
[("manifest:media-type", m)
,("manifest:full-path", fp)
+ ,("manifest:version", "1.2")
]
- let files = [ ent | ent <- filesInArchive archive, not ("META-INF" `isPrefixOf` ent) ]
+ let files = [ ent | ent <- filesInArchive archive,
+ not ("META-INF" `isPrefixOf` ent) ]
let manifestEntry = toEntry "META-INF/manifest.xml" epochtime
$ fromStringLazy $ render Nothing
$ text ""
$$
( inTags True "manifest:manifest"
- [("xmlns:manifest","urn:oasis:names:tc:opendocument:xmlns:manifest:1.0")]
+ [("xmlns:manifest","urn:oasis:names:tc:opendocument:xmlns:manifest:1.0")
+ ,("manifest:version","1.2")]
$ ( selfClosingTag "manifest:file-entry"
[("manifest:media-type","application/vnd.oasis.opendocument.text")
- ,("manifest:version","1.2")
,("manifest:full-path","/")]
$$ vcat ( map toFileEntry $ files )
)
@@ -107,7 +111,11 @@ writeODT opts doc@(Pandoc meta _) = do
)
)
)
- let archive'' = addEntryToArchive metaEntry archive'
+ -- make sure mimetype is first
+ let mimetypeEntry = toEntry "mimetype" epochtime
+ $ fromStringLazy "application/vnd.oasis.opendocument.text"
+ let archive'' = addEntryToArchive mimetypeEntry
+ $ addEntryToArchive metaEntry archive'
return $ fromArchive archive''
transformPic :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 05c576c20..3ec5c2073 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -461,7 +461,8 @@ tableStyle :: Int -> [(Char,Double)] -> Doc
tableStyle num wcs =
let tableId = "Table" ++ show (num + 1)
table = inTags True "style:style"
- [("style:name", tableId)] $
+ [("style:name", tableId)
+ ,("style:family", "table")] $
selfClosingTag "style:table-properties"
[("table:align" , "center")]
colStyle (c,0) = selfClosingTag "style:style"
diff --git a/tests/writer.opendocument b/tests/writer.opendocument
index 9e1661475..1cee01f76 100644
--- a/tests/writer.opendocument
+++ b/tests/writer.opendocument
@@ -1,5 +1,5 @@
-
+
--
cgit v1.2.3
From 3e8bd8aa15a57c3dc87772049aabedeb1e0c7582 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Wed, 14 Aug 2013 23:24:45 -0700
Subject: Updated for removed unMeta, unFormat in pandoc-types.
---
pandoc.cabal | 9 +++++++++
scripts/comments.py | 3 +--
scripts/myemph.py | 7 +++++--
scripts/tikz.py | 2 +-
src/Text/Pandoc/Writers/RST.hs | 4 ++--
tests/docbook-reader.native | 2 +-
tests/haddock-reader.native | 2 +-
tests/html-reader.native | 2 +-
tests/latex-reader.native | 8 ++++----
tests/markdown-reader-more.native | 10 +++++-----
tests/mediawiki-reader.native | 22 +++++++++++-----------
tests/opml-reader.native | 2 +-
tests/rst-reader.native | 8 ++++----
tests/s5.native | 2 +-
tests/testsuite.native | 38 +++++++++++++++++++-------------------
tests/textile-reader.native | 18 +++++++++---------
tests/writer.native | 38 +++++++++++++++++++-------------------
17 files changed, 94 insertions(+), 83 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/pandoc.cabal b/pandoc.cabal
index e22908918..352da4988 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -112,6 +112,15 @@ Extra-Source-Files:
-- generated man pages (produced post-build)
man/man1/pandoc.1,
man/man5/pandoc_markdown.5,
+ -- python library and sample python scripts
+ scripts/abc.py,
+ scripts/comments.py,
+ scripts/graphviz.py,
+ scripts/pandoc.py,
+ scripts/caps.py,
+ scripts/deemph.py,
+ scripts/myemph.py,
+ scripts/tikz.py,
-- tests
tests/bodybg.gif,
tests/docbook-reader.docbook
diff --git a/scripts/comments.py b/scripts/comments.py
index 304af1a2d..ded21039c 100755
--- a/scripts/comments.py
+++ b/scripts/comments.py
@@ -15,8 +15,7 @@ incomment = False
def comment(k,v,fmt):
global incomment
if k == 'RawBlock':
- f, s = v
- fmt = f['unFormat']
+ fmt, s = v
if fmt == "html":
if re.search("", s):
incomment = True
diff --git a/scripts/myemph.py b/scripts/myemph.py
index e527a0b2e..2a322b385 100755
--- a/scripts/myemph.py
+++ b/scripts/myemph.py
@@ -1,5 +1,5 @@
#!/usr/bin/env python
-from pandoc import toJSONFilter, rawInline
+from pandoc import toJSONFilter
"""
Pandoc filter that causes emphasis to be rendered using
@@ -7,9 +7,12 @@ the custom macro '\myemph{...}' rather than '\emph{...}'
in latex. Other output formats are unaffected.
"""
+def latex(s):
+ return {'RawInline': ['latex', s]}
+
def myemph(k, v, f):
if k == 'Emph' and f == 'latex':
- return [rawInline("latex", "\\myemph{")] + v + [rawInline("latex","}")]
+ return [latex('\\myemph{')] + v + [latex('}')]
if __name__ == "__main__":
toJSONFilter(myemph)
diff --git a/scripts/tikz.py b/scripts/tikz.py
index 7e1ed7927..4ff8b2383 100755
--- a/scripts/tikz.py
+++ b/scripts/tikz.py
@@ -44,7 +44,7 @@ def tikz2image(tikz, filetype, outfile):
def tikz(key, value, format):
if key == 'RawBlock':
[fmt, code] = value
- if fmt['unFormat'] == "latex" and re.match("\\\\begin{tikzpicture}", code):
+ if fmt == "latex" and re.match("\\\\begin{tikzpicture}", code):
outfile = imagedir + '/' + sha1(code)
if format == "html":
filetype = "png"
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 5fbbb6afc..557658bc8 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -176,10 +176,10 @@ blockToRST (Para inlines)
| otherwise = do
contents <- inlineListToRST inlines
return $ contents <> blankline
-blockToRST (RawBlock f str)
+blockToRST (RawBlock f@(Format f') str)
| f == "rst" = return $ text str
| otherwise = return $ blankline <> ".. raw:: " <>
- text (map toLower $ unFormat f) $+$
+ text (map toLower f') $+$
(nest 3 $ text str) $$ blankline
blockToRST HorizontalRule =
return $ blankline $$ "--------------" $$ blankline
diff --git a/tests/docbook-reader.native b/tests/docbook-reader.native
index 2d29bb154..8c94fea3e 100644
--- a/tests/docbook-reader.native
+++ b/tests/docbook-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
+Pandoc (Meta (fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]))
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,Header 1 ("",[],[]) [Str "Headers"]
,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")]
diff --git a/tests/haddock-reader.native b/tests/haddock-reader.native
index 877719b50..c17c2ddf0 100644
--- a/tests/haddock-reader.native
+++ b/tests/haddock-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList []})
+Pandoc (Meta (fromList []))
[Para [Str "This",Space,Str "file",Space,Str "tests",Space,Str "the",Space,Str "Pandoc",Space,Str "reader",Space,Str "for",Space,Str "Haddock.",Space,Str "We've",Space,Str "borrowed",Space,Str "examples",Space,Str "from",Space,Str "Haddock's",Space,Str "documentation:",Space,Link [Str "http://www.haskell.org/haddock/doc/html/ch03s08.html"] ("http://www.haskell.org/haddock/doc/html/ch03s08.html","http://www.haskell.org/haddock/doc/html/ch03s08.html"),Str "."]
,Para [Str "The",Space,Str "following",Space,Str "characters",Space,Str "have",Space,Str "special",Space,Str "meanings",Space,Str "in",Space,Str "Haddock,",Space,Str "/,",Space,Str "',",Space,Str "`,",Space,Str "\",",Space,Str "@,",Space,Str "<,",Space,Str "so",Space,Str "they",Space,Str "must",Space,Str "be",Space,Str "escaped."]
,Para [Str "*",Space,Str "This",Space,Str "is",Space,Str "a",Space,Str "paragraph,",Space,Str "not",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str ">",Space,Str "This",Space,Str "sentence",Space,Str "is",Space,Str "not",Space,Str "code.",Space,Str ">>>",Space,Str "This",Space,Str "is",Space,Str "not",Space,Str "an",Space,Str "example."]
diff --git a/tests/html-reader.native b/tests/html-reader.native
index 15937e594..8f60f040e 100644
--- a/tests/html-reader.native
+++ b/tests/html-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
+Pandoc (Meta (fromList [("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]))
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Str ".",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber",Str "'",Str "s",Space,Str "markdown",Space,Str "test",Space,Str "suite",Str "."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Headers"]
diff --git a/tests/latex-reader.native b/tests/latex-reader.native
index 504e8b701..ddee17f9e 100644
--- a/tests/latex-reader.native
+++ b/tests/latex-reader.native
@@ -1,5 +1,5 @@
-Pandoc (Meta {unMeta = fromList [("authors",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
-[RawBlock (Format {unFormat = "latex"}) "\\maketitle"
+Pandoc (Meta (fromList [("authors",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]))
+[RawBlock (Format "latex") "\\maketitle"
,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Headers"]
@@ -260,8 +260,8 @@ Pandoc (Meta {unMeta = fromList [("authors",MetaList [MetaInlines [Str "John",Sp
,HorizontalRule
,Header 1 ("",[],[]) [Str "LaTeX"]
,BulletList
- [[Para [Cite [Citation {citationId = "smith.1899", citationPrefix = [], citationSuffix = [Str "22-23"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [RawInline (Format {unFormat = "latex"}) "\\cite[22-23]{smith.1899}"]]]
- ,[Para [RawInline (Format {unFormat = "latex"}) "\\doublespacing"]]
+ [[Para [Cite [Citation {citationId = "smith.1899", citationPrefix = [], citationSuffix = [Str "22-23"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cite[22-23]{smith.1899}"]]]
+ ,[Para [RawInline (Format "latex") "\\doublespacing"]]
,[Para [Math InlineMath "2+2=4"]]
,[Para [Math InlineMath "x \\in y"]]
,[Para [Math InlineMath "\\alpha \\wedge \\omega"]]
diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native
index c88c0ed67..ca588571f 100644
--- a/tests/markdown-reader-more.native
+++ b/tests/markdown-reader-more.native
@@ -2,9 +2,9 @@
,Header 2 ("blank-line-before-url-in-link-reference",[],[]) [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"]
,Para [Link [Str "foo"] ("/url",""),Space,Str "and",Space,Link [Str "bar"] ("/url","title")]
,Header 2 ("raw-context-environments",[],[]) [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"]
-,Plain [RawInline (Format {unFormat = "tex"}) "\\placeformula "]
-,RawBlock (Format {unFormat = "context"}) "\\startformula\n L_{1} = L_{2}\n \\stopformula"
-,RawBlock (Format {unFormat = "context"}) "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
+,Plain [RawInline (Format "tex") "\\placeformula "]
+,RawBlock (Format "context") "\\startformula\n L_{1} = L_{2}\n \\stopformula"
+,RawBlock (Format "context") "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
,Header 2 ("urls-with-spaces",[],[]) [Str "URLs",Space,Str "with",Space,Str "spaces"]
,Para [Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("bar%20baz","title")]
,Para [Link [Str "baz"] ("/foo%20foo",""),Space,Link [Str "bam"] ("/foo%20fee",""),Space,Link [Str "bork"] ("/foo/zee%20zob","title")]
@@ -12,13 +12,13 @@
,HorizontalRule
,HorizontalRule
,Header 2 ("raw-html-before-header",[],[]) [Str "Raw",Space,Str "HTML",Space,Str "before",Space,Str "header"]
-,Para [RawInline (Format {unFormat = "html"}) "",RawInline (Format {unFormat = "html"}) ""]
+,Para [RawInline (Format "html") "",RawInline (Format "html") ""]
,Header 3 ("my-header",[],[]) [Str "my",Space,Str "header"]
,Header 2 ("in-math",[],[]) [Str "$",Space,Str "in",Space,Str "math"]
,Para [Math InlineMath "\\$2 + \\$3"]
,Header 2 ("commented-out-list-item",[],[]) [Str "Commented-out",Space,Str "list",Space,Str "item"]
,BulletList
- [[Plain [Str "one",Space,RawInline (Format {unFormat = "html"}) ""]]
+ [[Plain [Str "one",Space,RawInline (Format "html") ""]]
,[Plain [Str "three"]]]
,Header 2 ("backslash-newline",[],[]) [Str "Backslash",Space,Str "newline"]
,Para [Str "hi",LineBreak,Str "there"]
diff --git a/tests/mediawiki-reader.native b/tests/mediawiki-reader.native
index f6e09e45a..81596c7d7 100644
--- a/tests/mediawiki-reader.native
+++ b/tests/mediawiki-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList []})
+Pandoc (Meta (fromList []))
[Header 1 ("",[],[]) [Str "header"]
,Header 2 ("",[],[]) [Str "header",Space,Str "level",Space,Str "two"]
,Header 3 ("",[],[]) [Str "header",Space,Str "level",Space,Str "3"]
@@ -51,11 +51,11 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Str "bud"]
,Para [Str "another"]
,Header 2 ("",[],[]) [Str "raw",Space,Str "html"]
-,Para [Str "hi",Space,RawInline (Format {unFormat = "html"}) "",Emph [Str "there"],RawInline (Format {unFormat = "html"}) "",Str "."]
-,Para [RawInline (Format {unFormat = "html"}) "",Str "inserted",RawInline (Format {unFormat = "html"}) ""]
-,RawBlock (Format {unFormat = "html"}) ""
+,Para [Str "hi",Space,RawInline (Format "html") "
",Emph [Str "there"],RawInline (Format "html") "",Str "."]
+,Para [RawInline (Format "html") "
",Str "inserted",RawInline (Format "html") ""]
+,RawBlock (Format "html") "
"
,Para [Str "hi",Space,Emph [Str "there"]]
-,RawBlock (Format {unFormat = "html"}) "
"
+,RawBlock (Format "html") "
"
,Header 2 ("",[],[]) [Str "sup,",Space,Str "sub,",Space,Str "del"]
,Para [Str "H",Subscript [Str "2"],Str "O",Space,Str "base",Superscript [Emph [Str "exponent"]],Space,Strikeout [Str "hello"]]
,Header 2 ("",[],[]) [Str "inline",Space,Str "code"]
@@ -140,7 +140,7 @@ Pandoc (Meta {unMeta = fromList []})
,[Plain [Str "this",Space,Str "looks",Space,Str "like",Space,Str "a",Space,Str "continuation"]]
,[Plain [Str "and",Space,Str "is",Space,Str "often",Space,Str "used"]]
,[Plain [Str "instead",LineBreak,Str "of",Space,Str "
"]]])]]
- ,[Plain [RawInline (Format {unFormat = "mediawiki"}) "{{{template\n|author=John\n|title=My Book\n}}}"]
+ ,[Plain [RawInline (Format "mediawiki") "{{{template\n|author=John\n|title=My Book\n}}}"]
,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "five",Space,Str "sub",Space,Str "1"]
,OrderedList (1,DefaultStyle,DefaultDelim)
@@ -168,16 +168,16 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Code ("",[],[]) "\160hell\160\160\160\160\160\160yeah"]
,Para [Code ("",[],[]) "Start\160with\160a\160space\160in\160the\160first\160column,",LineBreak,Code ("",[],[]) "(before\160the\160).",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "Then\160your\160block\160format\160will\160be",LineBreak,Code ("",[],[]) "\160\160\160\160maintained.",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "This\160is\160good\160for\160copying\160in\160code\160blocks:",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "def\160function():",LineBreak,Code ("",[],[]) "\160\160\160\160\"\"\"documentation\160string\"\"\"",LineBreak,Code ("",[],[]) "",LineBreak,Code ("",[],[]) "\160\160\160\160if\160True:",LineBreak,Code ("",[],[]) "\160\160\160\160\160\160\160\160print\160True",LineBreak,Code ("",[],[]) "\160\160\160\160else:",LineBreak,Code ("",[],[]) "\160\160\160\160\160\160\160\160print\160False"]
,Para [Str "Not"]
-,RawBlock (Format {unFormat = "html"}) "
"
+,RawBlock (Format "html") "
"
,Para [Str "preformatted"]
,Para [Str "Don't",Space,Str "need"]
,Para [Code ("",[],[]) "a\160blank\160line"]
,Para [Str "around",Space,Str "a",Space,Str "preformatted",Space,Str "block."]
,Header 2 ("",[],[]) [Str "templates"]
-,RawBlock (Format {unFormat = "mediawiki"}) "{{Welcome}}"
-,RawBlock (Format {unFormat = "mediawiki"}) "{{Foo:Bar}}"
-,RawBlock (Format {unFormat = "mediawiki"}) "{{Thankyou|all your effort|Me}}"
-,Para [Str "Written",Space,RawInline (Format {unFormat = "mediawiki"}) "{{{date}}}",Space,Str "by",Space,RawInline (Format {unFormat = "mediawiki"}) "{{{name}}}",Str "."]
+,RawBlock (Format "mediawiki") "{{Welcome}}"
+,RawBlock (Format "mediawiki") "{{Foo:Bar}}"
+,RawBlock (Format "mediawiki") "{{Thankyou|all your effort|Me}}"
+,Para [Str "Written",Space,RawInline (Format "mediawiki") "{{{date}}}",Space,Str "by",Space,RawInline (Format "mediawiki") "{{{name}}}",Str "."]
,Header 2 ("",[],[]) [Str "tables"]
,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
[[]
diff --git a/tests/opml-reader.native b/tests/opml-reader.native
index e71857680..237a16719 100644
--- a/tests/opml-reader.native
+++ b/tests/opml-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Dave",Space,Str "Winer"]]),("date",MetaInlines [Str "Thu,",Space,Str "14",Space,Str "Jul",Space,Str "2005",Space,Str "23:41:05",Space,Str "GMT"]),("title",MetaInlines [Str "States"])]})
+Pandoc (Meta (fromList [("author",MetaList [MetaInlines [Str "Dave",Space,Str "Winer"]]),("date",MetaInlines [Str "Thu,",Space,Str "14",Space,Str "Jul",Space,Str "2005",Space,Str "23:41:05",Space,Str "GMT"]),("title",MetaInlines [Str "States"])]))
[Header 1 ("",[],[]) [Str "United",Space,Str "States"]
,Header 2 ("",[],[]) [Str "Far",Space,Str "West"]
,Header 3 ("",[],[]) [Str "Alaska"]
diff --git a/tests/rst-reader.native b/tests/rst-reader.native
index 69e73ae40..09da2d5ef 100644
--- a/tests/rst-reader.native
+++ b/tests/rst-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("authors",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("revision",MetaBlocks [Para [Str "3"]]),("subtitle",MetaInlines [Str "Subtitle"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
+Pandoc (Meta (fromList [("authors",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("revision",MetaBlocks [Para [Str "3"]]),("subtitle",MetaInlines [Str "Subtitle"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]))
[Header 1 ("",[],[]) [Str "Level",Space,Str "one",Space,Str "header"]
,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,Header 2 ("",[],[]) [Str "Level",Space,Str "two",Space,Str "header"]
@@ -172,11 +172,11 @@ Pandoc (Meta {unMeta = fromList [("authors",MetaList [MetaInlines [Str "John",Sp
[[Para [Str "123-4567"]]])]
,Header 1 ("",[],[]) [Str "HTML",Space,Str "Blocks"]
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
-,RawBlock (Format {unFormat = "html"}) "foo
"
+,RawBlock (Format "html") "foo
"
,Para [Str "Now,",Space,Str "nested:"]
-,RawBlock (Format {unFormat = "html"}) ""
+,RawBlock (Format "html") ""
,Header 1 ("",[],[]) [Str "LaTeX",Space,Str "Block"]
-,RawBlock (Format {unFormat = "latex"}) "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
+,RawBlock (Format "latex") "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
,Header 1 ("",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ".",Space,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str "."]
,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "",Str "."]
diff --git a/tests/s5.native b/tests/s5.native
index 5796b74a0..def09cf80 100644
--- a/tests/s5.native
+++ b/tests/s5.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Sam",Space,Str "Smith"],MetaInlines [Str "Jen",Space,Str "Jones"]]),("date",MetaInlines [Str "July",Space,Str "15,",Space,Str "2006"]),("title",MetaInlines [Str "My",Space,Str "S5",Space,Str "Document"])]})
+Pandoc (Meta (fromList [("author",MetaList [MetaInlines [Str "Sam",Space,Str "Smith"],MetaInlines [Str "Jen",Space,Str "Jones"]]),("date",MetaInlines [Str "July",Space,Str "15,",Space,Str "2006"]),("title",MetaInlines [Str "My",Space,Str "S5",Space,Str "Document"])]))
[Header 1 ("first-slide",[],[]) [Str "First",Space,Str "slide"]
,BulletList
[[Plain [Str "first",Space,Str "bullet"]]
diff --git a/tests/testsuite.native b/tests/testsuite.native
index f9cf606f3..503b3001e 100644
--- a/tests/testsuite.native
+++ b/tests/testsuite.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
+Pandoc (Meta (fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]))
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"]
@@ -228,45 +228,45 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "sublist"]]]]])]
,Header 1 ("html-blocks",[],[]) [Str "HTML",Space,Str "Blocks"]
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
-,RawBlock (Format {unFormat = "html"}) ""
+,RawBlock (Format "html") "
"
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n"
+,RawBlock (Format "html") "
\n"
,Para [Str "And",Space,Str "nested",Space,Str "without",Space,Str "indentation:"]
-,RawBlock (Format {unFormat = "html"}) "\n
\n
"
+,RawBlock (Format "html") "
\n
\n
"
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n
\n
"
+,RawBlock (Format "html") "
\n
\n
"
,Plain [Str "bar"]
-,RawBlock (Format {unFormat = "html"}) "
\n
\n"
+,RawBlock (Format "html") "
\n
\n"
,Para [Str "Interpreted",Space,Str "markdown",Space,Str "in",Space,Str "a",Space,Str "table:"]
-,RawBlock (Format {unFormat = "html"}) "\n\n"
+,RawBlock (Format "html") "\n\n| "
,Plain [Str "This",Space,Str "is",Space,Emph [Str "emphasized"]]
-,RawBlock (Format {unFormat = "html"}) " | \n"
+,RawBlock (Format "html") " | \n"
,Plain [Str "And",Space,Str "this",Space,Str "is",Space,Strong [Str "strong"]]
-,RawBlock (Format {unFormat = "html"}) " | \n \n \n\n\n"
+,RawBlock (Format "html") " | \n
\n
\n\n\n"
,Para [Str "Here\8217s",Space,Str "a",Space,Str "simple",Space,Str "block:"]
-,RawBlock (Format {unFormat = "html"}) "\n "
+,RawBlock (Format "html") "
\n "
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n"
+,RawBlock (Format "html") "
\n"
,Para [Str "This",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "code",Space,Str "block,",Space,Str "though:"]
,CodeBlock ("",[],[]) "\n foo\n
"
,Para [Str "As",Space,Str "should",Space,Str "this:"]
,CodeBlock ("",[],[]) "foo
"
,Para [Str "Now,",Space,Str "nested:"]
-,RawBlock (Format {unFormat = "html"}) "\n
\n
\n "
+,RawBlock (Format "html") "
\n
\n
\n "
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n
\n
\n"
+,RawBlock (Format "html") "
\n
\n
\n"
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
-,RawBlock (Format {unFormat = "html"}) "\n"
+,RawBlock (Format "html") "\n"
,Para [Str "Multiline:"]
-,RawBlock (Format {unFormat = "html"}) "\n\n\n"
+,RawBlock (Format "html") "\n\n\n"
,Para [Str "Code",Space,Str "block:"]
,CodeBlock ("",[],[]) ""
,Para [Str "Just",Space,Str "plain",Space,Str "comment,",Space,Str "with",Space,Str "trailing",Space,Str "spaces",Space,Str "on",Space,Str "the",Space,Str "line:"]
-,RawBlock (Format {unFormat = "html"}) " \n"
+,RawBlock (Format "html") " \n"
,Para [Str "Code:"]
,CodeBlock ("",[],[]) "
"
,Para [Str "Hr\8217s:"]
-,RawBlock (Format {unFormat = "html"}) "
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n"
+,RawBlock (Format "html") "
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n"
,HorizontalRule
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
@@ -294,7 +294,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,HorizontalRule
,Header 1 ("latex",[],[]) [Str "LaTeX"]
,BulletList
- [[Plain [RawInline (Format {unFormat = "tex"}) "\\cite[22-23]{smith.1899}"]]
+ [[Plain [RawInline (Format "tex") "\\cite[22-23]{smith.1899}"]]
,[Plain [Math InlineMath "2+2=4"]]
,[Plain [Math InlineMath "x \\in y"]]
,[Plain [Math InlineMath "\\alpha \\wedge \\omega"]]
@@ -309,7 +309,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "Shoes",Space,Str "($20)",Space,Str "and",Space,Str "socks",Space,Str "($5)."]]
,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
-,RawBlock (Format {unFormat = "latex"}) "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
+,RawBlock (Format "latex") "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
,HorizontalRule
,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
diff --git a/tests/textile-reader.native b/tests/textile-reader.native
index 70b33f31d..31ab558d7 100644
--- a/tests/textile-reader.native
+++ b/tests/textile-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList []})
+Pandoc (Meta (fromList []))
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Space,Str "Textile",Space,Str "Reader",Str ".",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber",Str "\8217",Str "s",Space,Str "markdown",Space,Str "test",Space,Str "suite",Str "."]
,HorizontalRule
,Header 1 ("",[],[]) [Str "Headers"]
@@ -137,23 +137,23 @@ Pandoc (Meta {unMeta = fromList []})
,Header 1 ("",[],[]) [Str "Entities"]
,Para [Str "*",LineBreak,Str "&"]
,Header 1 ("",[],[]) [Str "Raw",Space,Str "HTML"]
-,Para [Str "However",Str ",",Space,RawInline (Format {unFormat = "html"}) "",Space,Str "raw",Space,Str "HTML",Space,Str "inlines",Space,RawInline (Format {unFormat = "html"}) "",Space,Str "are",Space,Str "accepted",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str ":"]
-,RawBlock (Format {unFormat = "html"}) ""
+,Para [Str "However",Str ",",Space,RawInline (Format "html") "
",Space,Str "raw",Space,Str "HTML",Space,Str "inlines",Space,RawInline (Format "html") "",Space,Str "are",Space,Str "accepted",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str ":"]
+,RawBlock (Format "html") "
"
,Para [Str "any",Space,Strong [Str "Raw",Space,Str "HTML",Space,Str "Block"],Space,Str "with",Space,Str "bold"]
-,RawBlock (Format {unFormat = "html"}) "
"
+,RawBlock (Format "html") "
"
,Para [Str "Html",Space,Str "blocks",Space,Str "can",Space,Str "be"]
-,RawBlock (Format {unFormat = "html"}) ""
+,RawBlock (Format "html") "
"
,Para [Str "inlined"]
-,RawBlock (Format {unFormat = "html"}) "
"
+,RawBlock (Format "html") "
"
,Para [Str "as",Space,Str "well",Str "."]
,BulletList
[[Plain [Str "this",Space,Str "<",Str "div",Str ">",Space,Str "won",Str "\8217",Str "t",Space,Str "produce",Space,Str "raw",Space,Str "html",Space,Str "blocks",Space,Str "<",Str "/div",Str ">"]]
- ,[Plain [Str "but",Space,Str "this",Space,RawInline (Format {unFormat = "html"}) "",Space,Str "will",Space,Str "produce",Space,Str "inline",Space,Str "html",Space,RawInline (Format {unFormat = "html"}) ""]]]
+ ,[Plain [Str "but",Space,Str "this",Space,RawInline (Format "html") "",Space,Str "will",Space,Str "produce",Space,Str "inline",Space,Str "html",Space,RawInline (Format "html") ""]]]
,Para [Str "Can",Space,Str "you",Space,Str "prove",Space,Str "that",Space,Str "2",Space,Str "<",Space,Str "3",Space,Str "?"]
,Header 1 ("",[],[]) [Str "Raw",Space,Str "LaTeX"]
,Para [Str "This",Space,Str "Textile",Space,Str "reader",Space,Str "also",Space,Str "accepts",Space,Str "raw",Space,Str "LaTeX",Space,Str "for",Space,Str "blocks",Space,Str ":"]
-,RawBlock (Format {unFormat = "latex"}) "\\begin{itemize}\n \\item one\n \\item two\n\\end{itemize}"
-,Para [Str "and",Space,Str "for",Space,RawInline (Format {unFormat = "latex"}) "\\emph{inlines}",Str "."]
+,RawBlock (Format "latex") "\\begin{itemize}\n \\item one\n \\item two\n\\end{itemize}"
+,Para [Str "and",Space,Str "for",Space,RawInline (Format "latex") "\\emph{inlines}",Str "."]
,Header 1 ("",[],[]) [Str "Acronyms",Space,Str "and",Space,Str "marks"]
,Para [Str "PBS (Public Broadcasting System)"]
,Para [Str "Hi",Str "\8482"]
diff --git a/tests/writer.native b/tests/writer.native
index f9cf606f3..503b3001e 100644
--- a/tests/writer.native
+++ b/tests/writer.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
+Pandoc (Meta (fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]))
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"]
@@ -228,45 +228,45 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "sublist"]]]]])]
,Header 1 ("html-blocks",[],[]) [Str "HTML",Space,Str "Blocks"]
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
-,RawBlock (Format {unFormat = "html"}) ""
+,RawBlock (Format "html") "
"
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n"
+,RawBlock (Format "html") "
\n"
,Para [Str "And",Space,Str "nested",Space,Str "without",Space,Str "indentation:"]
-,RawBlock (Format {unFormat = "html"}) "\n
\n
"
+,RawBlock (Format "html") "
\n
\n
"
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n
\n
"
+,RawBlock (Format "html") "
\n
\n
"
,Plain [Str "bar"]
-,RawBlock (Format {unFormat = "html"}) "
\n
\n"
+,RawBlock (Format "html") "
\n
\n"
,Para [Str "Interpreted",Space,Str "markdown",Space,Str "in",Space,Str "a",Space,Str "table:"]
-,RawBlock (Format {unFormat = "html"}) "\n\n"
+,RawBlock (Format "html") "\n\n| "
,Plain [Str "This",Space,Str "is",Space,Emph [Str "emphasized"]]
-,RawBlock (Format {unFormat = "html"}) " | \n"
+,RawBlock (Format "html") " | \n"
,Plain [Str "And",Space,Str "this",Space,Str "is",Space,Strong [Str "strong"]]
-,RawBlock (Format {unFormat = "html"}) " | \n \n \n\n\n"
+,RawBlock (Format "html") " | \n
\n
\n\n\n"
,Para [Str "Here\8217s",Space,Str "a",Space,Str "simple",Space,Str "block:"]
-,RawBlock (Format {unFormat = "html"}) "\n "
+,RawBlock (Format "html") "
\n "
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n"
+,RawBlock (Format "html") "
\n"
,Para [Str "This",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "code",Space,Str "block,",Space,Str "though:"]
,CodeBlock ("",[],[]) "\n foo\n
"
,Para [Str "As",Space,Str "should",Space,Str "this:"]
,CodeBlock ("",[],[]) "foo
"
,Para [Str "Now,",Space,Str "nested:"]
-,RawBlock (Format {unFormat = "html"}) "\n
\n
\n "
+,RawBlock (Format "html") "
\n
\n
\n "
,Plain [Str "foo"]
-,RawBlock (Format {unFormat = "html"}) "
\n
\n
\n"
+,RawBlock (Format "html") "
\n
\n
\n"
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
-,RawBlock (Format {unFormat = "html"}) "\n"
+,RawBlock (Format "html") "\n"
,Para [Str "Multiline:"]
-,RawBlock (Format {unFormat = "html"}) "\n\n\n"
+,RawBlock (Format "html") "\n\n\n"
,Para [Str "Code",Space,Str "block:"]
,CodeBlock ("",[],[]) ""
,Para [Str "Just",Space,Str "plain",Space,Str "comment,",Space,Str "with",Space,Str "trailing",Space,Str "spaces",Space,Str "on",Space,Str "the",Space,Str "line:"]
-,RawBlock (Format {unFormat = "html"}) " \n"
+,RawBlock (Format "html") " \n"
,Para [Str "Code:"]
,CodeBlock ("",[],[]) "
"
,Para [Str "Hr\8217s:"]
-,RawBlock (Format {unFormat = "html"}) "
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n"
+,RawBlock (Format "html") "
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n\n
\n"
,HorizontalRule
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
@@ -294,7 +294,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,HorizontalRule
,Header 1 ("latex",[],[]) [Str "LaTeX"]
,BulletList
- [[Plain [RawInline (Format {unFormat = "tex"}) "\\cite[22-23]{smith.1899}"]]
+ [[Plain [RawInline (Format "tex") "\\cite[22-23]{smith.1899}"]]
,[Plain [Math InlineMath "2+2=4"]]
,[Plain [Math InlineMath "x \\in y"]]
,[Plain [Math InlineMath "\\alpha \\wedge \\omega"]]
@@ -309,7 +309,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "Shoes",Space,Str "($20)",Space,Str "and",Space,Str "socks",Space,Str "($5)."]]
,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
-,RawBlock (Format {unFormat = "latex"}) "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
+,RawBlock (Format "latex") "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
,HorizontalRule
,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
--
cgit v1.2.3
From 441a7aebf8c141612203d1cab0032f8c55e536ed Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Fri, 16 Aug 2013 13:02:55 -0700
Subject: LaTeX writer: Avoid problem with footnotes in unnumbered headers.
Closes #940.
Added test case.
---
src/Text/Pandoc/Writers/LaTeX.hs | 13 +++++++------
tests/Tests/Writers/LaTeX.hs | 6 ++++++
2 files changed, 13 insertions(+), 6 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 7f9a99801..98553c421 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -498,14 +498,15 @@ sectionHeader unnumbered ref level lst = do
let noNote (Note _) = Str ""
noNote x = x
let lstNoNotes = walk noNote lst
+ txtNoNotes <- inlineListToLaTeX lstNoNotes
let star = if unnumbered then text "*" else empty
- -- footnotes in sections don't work unless you specify an optional
- -- argument: \section[mysec]{mysec\footnote{blah}}
- optional <- if lstNoNotes == lst
+ -- footnotes in sections don't work (except for starred variants)
+ -- unless you specify an optional argument:
+ -- \section[mysec]{mysec\footnote{blah}}
+ optional <- if unnumbered || lstNoNotes == lst
then return empty
else do
- res <- inlineListToLaTeX lstNoNotes
- return $ char '[' <> res <> char ']'
+ return $ brackets txtNoNotes
let stuffing = star <> optional <> braces txt
book <- gets stBook
opts <- gets stOptions
@@ -536,7 +537,7 @@ sectionHeader unnumbered ref level lst = do
$$ if unnumbered
then "\\addcontentsline{toc}" <>
braces (text sectionType) <>
- braces txt
+ braces txtNoNotes
else empty
-- | Convert list of inline elements to LaTeX.
diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs
index b1427d91f..ebde5b97c 100644
--- a/tests/Tests/Writers/LaTeX.hs
+++ b/tests/Tests/Writers/LaTeX.hs
@@ -36,4 +36,10 @@ tests = [ testGroup "code blocks"
[ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
"$\\sigma|_{\\{x\\}}$"
]
+ , testGroup "headers"
+ [ "unnumbered header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header 1" <> note (plain $ text "note")) =?>
+ "\\section*{Header 1\\footnote{note}}\\label{foo}\n\\addcontentsline{toc}{section}{Header 1}\n"
+ ]
]
--
cgit v1.2.3
From 8d441af3da4709fd48a44e860d5a0cd4d35792af Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 18 Aug 2013 14:36:40 -0700
Subject: Adjusted writers and tests for change in parsing of div/span.
Textile, MediaWiki, Markdown, Org, RST will emit raw HTML div tags for divs.
Otherwise Div and Span are "transparent" block containers.
---
src/Text/Pandoc/Writers/Docbook.hs | 2 +-
src/Text/Pandoc/Writers/Markdown.hs | 17 ++++++++++-----
src/Text/Pandoc/Writers/MediaWiki.hs | 12 +++++++----
src/Text/Pandoc/Writers/Org.hs | 9 +++++++-
src/Text/Pandoc/Writers/RST.hs | 6 +++++-
src/Text/Pandoc/Writers/Shared.hs | 18 ++++++++++++++++
src/Text/Pandoc/Writers/Textile.hs | 8 ++++++--
tests/testsuite.native | 18 ++++------------
tests/testsuite.txt | 12 +++++------
tests/writer.docbook | 40 ++++++++++++++----------------------
tests/writer.fb2 | 2 +-
tests/writer.html | 12 +++--------
tests/writer.markdown | 27 +++++++++++++++++++-----
tests/writer.mediawiki | 28 +++++++++++++++++--------
tests/writer.native | 18 ++++------------
tests/writer.opml | 2 +-
tests/writer.org | 35 ++++++++++++++++++++++++++-----
tests/writer.plain | 5 +++++
tests/writer.rst | 35 ++++++++++++++++++++++++++-----
tests/writer.textile | 31 +++++++++++++++++++++++-----
20 files changed, 225 insertions(+), 112 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 3d150d19b..7c03c07dc 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -149,7 +149,7 @@ listItemToDocbook opts item =
-- | Convert a Pandoc block element to Docbook.
blockToDocbook :: WriterOptions -> Block -> Doc
blockToDocbook _ Null = empty
-blockToDocbook opts (Div _ bs) = blocksToDocbook opts bs
+blockToDocbook opts (Div _ bs) = blocksToDocbook opts $ map plainToPara bs
blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
-- title beginning with fig: indicates that the image is a figure
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 3d0ed8702..623c445df 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables #-}
{-
-Copyright (C) 2006-2010 John MacFarlane
+Copyright (C) 2006-2013 John MacFarlane
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Markdown
- Copyright : Copyright (C) 2006-2010 John MacFarlane
+ Copyright : Copyright (C) 2006-2013 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane
@@ -301,7 +301,13 @@ blockToMarkdown :: WriterOptions -- ^ Options
-> Block -- ^ Block element
-> State WriterState Doc
blockToMarkdown _ Null = return empty
-blockToMarkdown opts (Div _ bs) = blockListToMarkdown opts bs
+blockToMarkdown opts (Div attrs ils) = do
+ isPlain <- gets stPlain
+ contents <- blockListToMarkdown opts ils
+ return $ if isPlain
+ then contents <> blankline
+ else tagWithAttrs "div" attrs <> blankline <>
+ contents <> blankline <> " " <> blankline
blockToMarkdown opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
return $ contents <> cr
@@ -629,8 +635,9 @@ escapeSpaces x = x
-- | Convert Pandoc inline element to markdown.
inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc
-inlineToMarkdown opts (Span _ ils) =
- inlineListToMarkdown opts ils
+inlineToMarkdown opts (Span attrs ils) = do
+ contents <- inlineListToMarkdown opts ils
+ return $ tagWithAttrs "span" attrs <> contents <> text ""
inlineToMarkdown opts (Emph lst) = do
contents <- inlineListToMarkdown opts lst
return $ "*" <> contents <> "*"
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 4ffba1100..61741a61e 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -34,6 +34,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
+import Text.Pandoc.Pretty (render)
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.XML ( escapeStringForXML )
import Data.List ( intersect, intercalate, intersperse )
@@ -83,8 +84,10 @@ blockToMediaWiki :: WriterOptions -- ^ Options
blockToMediaWiki _ Null = return ""
-blockToMediaWiki opts (Div _ bs) =
- blockListToMediaWiki opts bs
+blockToMediaWiki opts (Div attrs bs) = do
+ contents <- blockListToMediaWiki opts bs
+ return $ render Nothing (tagWithAttrs "div" attrs) ++ "\n\n" ++
+ contents ++ "\n\n" ++ ""
blockToMediaWiki opts (Plain inlines) =
inlineListToMediaWiki opts inlines
@@ -332,8 +335,9 @@ inlineListToMediaWiki opts lst =
-- | Convert Pandoc inline element to MediaWiki.
inlineToMediaWiki :: WriterOptions -> Inline -> State WriterState String
-inlineToMediaWiki opts (Span _ ils) =
- inlineListToMediaWiki opts ils
+inlineToMediaWiki opts (Span attrs ils) = do
+ contents <- inlineListToMediaWiki opts ils
+ return $ render Nothing (tagWithAttrs "span" attrs) ++ contents ++ ""
inlineToMediaWiki opts (Emph lst) = do
contents <- inlineListToMediaWiki opts lst
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 34ae532b0..51083f52b 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -106,7 +106,14 @@ escapeString = escapeStringUsing $
blockToOrg :: Block -- ^ Block element
-> State WriterState Doc
blockToOrg Null = return empty
-blockToOrg (Div _ bs) = blockListToOrg bs
+blockToOrg (Div attrs bs) = do
+ contents <- blockListToOrg bs
+ let startTag = tagWithAttrs "div" attrs
+ let endTag = text ""
+ return $ blankline $$ "#+BEGIN_HTML" $$
+ nest 2 startTag $$ "#+END_HTML" $$ blankline $$
+ contents $$ blankline $$ "#+BEGIN_HTML" $$
+ nest 2 endTag $$ "#+END_HTML" $$ blankline
blockToOrg (Plain inlines) = inlineListToOrg inlines
-- title beginning with fig: indicates that the image is a figure
blockToOrg (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 557658bc8..70c6b4421 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -161,7 +161,11 @@ bordered contents c =
blockToRST :: Block -- ^ Block element
-> State WriterState Doc
blockToRST Null = return empty
-blockToRST (Div _ bs) = blockListToRST bs
+blockToRST (Div attr bs) = do
+ contents <- blockListToRST bs
+ let startTag = ".. raw:: html" $+$ nest 3 (tagWithAttrs "div" attr)
+ let endTag = ".. raw:: html" $+$ nest 3 ""
+ return $ blankline <> startTag $+$ contents $+$ endTag $$ blankline
blockToRST (Plain inlines) = inlineListToRST inlines
-- title beginning with fig: indicates that the image is a figure
blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index e6ec853f8..89923822c 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2013 John MacFarlane
@@ -32,9 +33,12 @@ module Text.Pandoc.Writers.Shared (
, getField
, setField
, defField
+ , tagWithAttrs
)
where
import Text.Pandoc.Definition
+import Text.Pandoc.Pretty
+import Text.Pandoc.XML (escapeStringForXML)
import Control.Monad (liftM)
import Text.Pandoc.Options (WriterOptions(..))
import qualified Data.HashMap.Strict as H
@@ -120,3 +124,17 @@ defField field val (Object hashmap) =
where f _newval oldval = oldval
defField _ _ x = x
+-- Produce an HTML tag with the given pandoc attributes.
+tagWithAttrs :: String -> Attr -> Doc
+tagWithAttrs tag (ident,classes,kvs) = hsep
+ ["<" <> text tag
+ ,if null ident
+ then empty
+ else "id=" <> doubleQuotes (text ident)
+ ,if null classes
+ then empty
+ else "class=" <> doubleQuotes (text (unwords classes))
+ ]
+ <> hsep (map (\(k,v) -> text k <> "=" <>
+ doubleQuotes (text (escapeStringForXML v))) kvs)
+ <> ">"
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 27e8b60ec..7c102cc86 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -33,6 +33,7 @@ module Text.Pandoc.Writers.Textile ( writeTextile ) where
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared
+import Text.Pandoc.Pretty (render)
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.XML ( escapeStringForXML )
@@ -101,8 +102,11 @@ blockToTextile :: WriterOptions -- ^ Options
blockToTextile _ Null = return ""
-blockToTextile opts (Div _ bs) =
- blockListToTextile opts bs
+blockToTextile opts (Div attr bs) = do
+ let startTag = render Nothing $ tagWithAttrs "div" attr
+ let endTag = ""
+ contents <- blockListToTextile opts bs
+ return $ startTag ++ "\n\n" ++ contents ++ "\n\n" ++ endTag ++ "\n"
blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines
diff --git a/tests/testsuite.native b/tests/testsuite.native
index d1b14b24e..678d7595f 100644
--- a/tests/testsuite.native
+++ b/tests/testsuite.native
@@ -228,15 +228,9 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "sublist"]]]]])]
,Header 1 ("html-blocks",[],[]) [Str "HTML",Space,Str "Blocks"]
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
-,RawBlock (Format "html") ""
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n"
+,Div ("",[],[]) [Plain [Str "foo"]]
,Para [Str "And",Space,Str "nested",Space,Str "without",Space,Str "indentation:"]
-,RawBlock (Format "html") "\n
\n
"
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n
\n
"
-,Plain [Str "bar"]
-,RawBlock (Format "html") "
\n
\n"
+,Div ("",[],[]) [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "foo"]]],Div ("",[],[]) [Plain [Str "bar"]]]
,Para [Str "Interpreted",Space,Str "markdown",Space,Str "in",Space,Str "a",Space,Str "table:"]
,RawBlock (Format "html") "\n\n| "
,Plain [Str "This",Space,Str "is",Space,Emph [Str "emphasized"]]
@@ -244,17 +238,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Plain [Str "And",Space,Str "this",Space,Str "is",Space,Strong [Str "strong"]]
,RawBlock (Format "html") " | \n
\n
\n\n\n"
,Para [Str "Here\8217s",Space,Str "a",Space,Str "simple",Space,Str "block:"]
-,RawBlock (Format "html") "\n "
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n"
+,Div ("",[],[]) [Plain [Str "foo"]]
,Para [Str "This",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "code",Space,Str "block,",Space,Str "though:"]
,CodeBlock ("",[],[]) "\n foo\n
"
,Para [Str "As",Space,Str "should",Space,Str "this:"]
,CodeBlock ("",[],[]) "foo
"
,Para [Str "Now,",Space,Str "nested:"]
-,RawBlock (Format "html") "\n
\n
\n "
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n
\n
\n"
+,Div ("",[],[]) [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "foo"]]]]
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
,RawBlock (Format "html") "\n"
,Para [Str "Multiline:"]
diff --git a/tests/testsuite.txt b/tests/testsuite.txt
index 3bb5d8cb5..4ddaae23f 100644
--- a/tests/testsuite.txt
+++ b/tests/testsuite.txt
@@ -377,7 +377,7 @@ Interpreted markdown in a table:
Here's a simple block:
- foo
+foo
This should be a code block, though:
@@ -393,11 +393,11 @@ As should this:
Now, nested:
This should just be an HTML comment:
diff --git a/tests/writer.docbook b/tests/writer.docbook
index 1e77a61ed..e427d8ffc 100644
--- a/tests/writer.docbook
+++ b/tests/writer.docbook
@@ -862,22 +862,18 @@ These should not be escaped: \$ \\ \> \[ \{
Simple block on one line:
-
- foo
-
+
+ foo
+
And nested without indentation:
-
+
+ foo
+
+
+ bar
+
Interpreted markdown in a table:
@@ -896,10 +892,9 @@ These should not be escaped: \$ \\ \> \[ \{
Here’s a simple block:
-
-
- foo
-
+
+ foo
+
This should be a code block, though:
@@ -917,14 +912,9 @@ These should not be escaped: \$ \\ \> \[ \{
Now, nested:
-
+
+ foo
+
This should just be an HTML comment:
diff --git a/tests/writer.fb2 b/tests/writer.fb2
index 0bcbf1c2a..8106d2b91 100644
--- a/tests/writer.fb2
+++ b/tests/writer.fb2
@@ -1,2 +1,2 @@
-Pandoc Test SuiteJohnMacFarlaneAnonymousJuly 17, 2006pandocPandoc Test Suite
John MacFarlane
Anonymous
July 17, 2006
This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.
——————————
Headers
Level 2 with an embedded link </url>
Level 1
Level 2 with emphasis
Level 3
with no blank line
Level 2
with no blank line
——————————
Paragraphs
Here’s a regular paragraph.
In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.
Here’s one with a bullet. * criminey.
There should be a hard line breakhere.
——————————
Block Quotes
E-mail style:
This is a block quote. It is pretty short.
Code in a block quote:
sub status {
print "working";
}
A list:
1. item one
2. item two
Nested block quotes:
nested
nested
This should not be a block quote: 2 > 1.
And a following paragraph.
——————————
Code Blocks
Code:
---- (should be four hyphens)
sub status {
print "working";
}
this code block is indented by one tab
And:
this code block is indented by two tabs
These should not be escaped: \$ \\ \> \[ \{
——————————
Lists
Unordered
Asterisks tight:
• asterisk 1
• asterisk 2
• asterisk 3
Asterisks loose:
• asterisk 1
• asterisk 2
• asterisk 3
Pluses tight:
• Plus 1
• Plus 2
• Plus 3
Pluses loose:
• Plus 1
• Plus 2
• Plus 3
Minuses tight:
• Minus 1
• Minus 2
• Minus 3
Minuses loose:
• Minus 1
• Minus 2
• Minus 3
Ordered
Tight:
1. First
2. Second
3. Third
and:
1. One
2. Two
3. Three
Loose using tabs:
1. First
2. Second
3. Third
and using spaces:
1. One
2. Two
3. Three
Multiple paragraphs:
1. Item 1, graf one.Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
2. Item 2.
3. Item 3.
Here’s another:
1. First
2. Second:
• Fee
• Fie
• Foe
3. Third
Same thing but with paragraphs:
1. First
2. Second:
• Fee
• Fie
• Foe
3. Third
Tabs and spaces
• this is a list item indented with tabs
• this is a list item indented with spaces
◦ this is an example list item indented with tabs
◦ this is an example list item indented with spaces
Fancy list markers
(2) begins with 2
(3) and now 3with a continuation
(3) iv. sublist with roman numerals, starting with 4
(3) v. more items
(3) v. (A) a subsublist
(3) v. (B) a subsublist
Nesting:
A. Upper Alpha
A. I. Upper Roman.
A. I. (6) Decimal start with 6
A. I. (6) c) Lower alpha with paren
Autonumbering:
1. Autonumber.
2. More.
2. 1. Nested.
Should not be a list item:
M.A. 2007
B. Williams
——————————
Definition Lists
Tight using spaces:
apple
red fruit
orange
orange fruit
banana
yellow fruit
Tight using tabs:
apple
red fruit
orange
orange fruit
banana
yellow fruit
Loose:
apple
red fruit
orange
orange fruit
banana
yellow fruit
Multiple blocks with italics:
apple
red fruit contains seeds, crisp, pleasant to taste
orange
orange fruit
{ orange code block }
orange block quote
Multiple definitions, tight:
apple
red fruit computer
orange
orange fruit bank
Multiple definitions, loose:
apple
red fruit computer
orange
orange fruit bank
Blank line after term, indented marker, alternate markers:
apple
red fruit computer
orange
orange fruit
1. sublist
2. sublist
HTML Blocks
Simple block on one line:
<div>
foo</div>
And nested without indentation:
<div>
<div>
<div>
foo</div>
</div>
<div>
bar</div>
</div>
Interpreted markdown in a table:
<table>
<tr>
<td>
This is emphasized</td>
<td>
And this is strong</td>
</tr>
</table>
<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
Here’s a simple block:
<div>
foo</div>
This should be a code block, though:
<div>
foo
</div>
As should this:
<div>foo</div>
Now, nested:
<div>
<div>
<div>
foo</div>
</div>
</div>
This should just be an HTML comment:
<!-- Comment -->
Multiline:
<!--
Blah
Blah
-->
<!--
This is another comment.
-->
Code block:
<!-- Comment -->
Just plain comment, with trailing spaces on the line:
<!-- foo -->
Code:
<hr />
Hr’s:
<hr>
<hr />
<hr />
<hr>
<hr />
<hr />
<hr class="foo" id="bar" />
<hr class="foo" id="bar" />
<hr class="foo" id="bar">
——————————
Inline Markup
This is emphasized, and so is this.
This is strong, and so is this.
An emphasized link[1].
This is strong and em.
So is this word.
This is strong and em.
So is this word.
This is code: >, $, \, \$, <html>.
This is strikeout.
Superscripts: abcd ahello ahello there.
Subscripts: H2O, H23O, Hmany of themO.
These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.
——————————
Smart quotes, ellipses, dashes
“Hello,” said the spider. “‘Shelob’ is my name.”
‘A’, ‘B’, and ‘C’ are letters.
‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’
‘He said, “I want to go.”’ Were you alive in the 70’s?
Here is some quoted ‘code’ and a “quoted link[2]”.
Some dashes: one—two — three—four — five.
Dashes between numbers: 5–7, 255–66, 1987–1999.
Ellipses…and…and….
——————————
LaTeX
•
• 2+2=4
• x \in y
• \alpha \wedge \omega
• 223
• p-Tree
• Here’s some display math: \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}
• Here’s one that has a line break in it: \alpha + \omega \times x^2.
These shouldn’t be math:
• To get the famous equation, write $e = mc^2$.
• $22,000 is a lot of money. So is $34,000. (It worked if “lot” is emphasized.)
• Shoes ($20) and socks ($5).
• Escaped $: $73 this should be emphasized 23$.
Here’s a LaTeX table:
\begin{tabular}{|l|l|}\hline
Animal & Number \\ \hline
Dog & 2 \\
Cat & 1 \\ \hline
\end{tabular}
——————————
Special Characters
Here is some unicode:
• I hat: Î
• o umlaut: ö
• section: §
• set membership: ∈
• copyright: ©
AT&T has an ampersand in their name.
AT&T is another way to write it.
This & that.
4 < 5.
6 > 5.
Backslash: \
Backtick: `
Asterisk: *
Underscore: _
Left brace: {
Right brace: }
Left bracket: [
Right bracket: ]
Left paren: (
Right paren: )
Greater-than: >
Hash: #
Period: .
Bang: !
Plus: +
Minus: -
——————————
Links
Explicit
Just a URL[3].
URL and title[4].
URL and title[5].
URL and title[6].
URL and title[7]
URL and title[8]
with_underscore[9]
Email link[10]
Empty[11].
Reference
Foo bar[12].
Foo bar[13].
Foo bar[14].
With embedded [brackets][15].
b[16] by itself should be a link.
Indented once[17].
Indented twice[18].
Indented thrice[19].
This should [not][] be a link.
[not]: /url
Foo bar[20].
Foo biz[21].
With ampersands
Here’s a link with an ampersand in the URL[22].
Here’s a link with an amersand in the link text: AT&T[23].
Here’s an inline link[24].
Here’s an inline link in pointy braces[25].
Autolinks
With an ampersand: http://example.com/?foo=1&bar=2[26]
• In a list?
• http://example.com/[27]
• It should.
An e-mail address: nobody@nowhere.net[28]
Blockquoted: http://example.com/[29]
Auto-links should not occur here: <http://example.com/>
or here: <http://example.com/>
——————————
Images
From “Voyage dans la Lune” by Georges Melies (1902):
Here is a movie icon.
——————————
Footnotes
Here is a footnote reference,[30] and another.[31] This should not be a footnote reference, because it contains a space.[^my note] Here is an inline note.[32]
Notes can go in quotes.[33]
1. And in list items.[34]
This paragraph should not be part of the note, as it is not indented.
2
http://example.com/?foo=1&bar=2
5
title preceded by two spaces: /url/
6
title preceded by a tab: /url/
7
title with "quotes" in it: /url/
8
title with single quotes: /url/
10
mailto:nobody@nowhere.net
20
Title with "quotes" inside: /url/
21
Title with "quote" inside: /url/
22
http://example.com/?foo=1&bar=2
26
http://example.com/?foo=1&bar=2
28
mailto:nobody@nowhere.net
30
Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.
31
Here’s the long note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the footnote (as with list items).
{ <code> }
If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.
32
This is easier to type. Inline notes may contain links[32] and ] verbatim characters, as well as [bracketed text].
/9j/4AAQSkZJRgABAQEASABIAAD//gBQVGhpcyBhcnQgaXMgaW4gdGhlIHB1YmxpYyBkb21haW4uIEtldmluIEh1Z2hlcywga2V2aW5oQGVpdC5jb20sIFNlcHRlbWJlciAxOTk1/9sAQwABAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/9sAQwEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/8AAEQgAFgAUAwEiAAIRAQMRAf/EABoAAQACAwEAAAAAAAAAAAAAAAAICQUGCgf/xAAjEAABBQEAAwABBQAAAAAAAAAGAwQFBwgCAAEJChEVOXa3/8QAFgEBAQEAAAAAAAAAAAAAAAAABggA/8QAJhEBAAECBQEJAAAAAAAAAAAAAQIAAwQFBhEhszE0NlFUcXR1tP/aAAwDAQACEQMRAD8AqQzziPNmpiqnIO1q4H+WkB84MdlzRSuM82/jVw/JCORtRmQz5d2VTy6WmS2eSYx3U/qkSRbgFsqRzH2Is4/mCluXc33vy8xTnJjTNqV/T8LKmkhr8Hq1da2aOvTfIh2CFeNt+GxFBP8AJFdFUbPWh+4FdXV7OtZOMR7mK9lBWNN+JBmMQ5cwmfH8DEFhTZUCRlE6CBq/ds/nBh9oYygeY1L9FnCUnBSN1t+w0l9bNomx1cllsOrL9OCTKtKOIqua6UVjP0dEvTyM7gp/3whbkAD0ScX3r6MLg+C2/XsMhCnJRn/5cVNHyJHiX6JKIFhhqnFeagm9BIgjfcJyNBTZiROBUk6Mp8CJRmT4NWU2MatV7n495DPk/wAbMJSRJOTBDItq0KR5s/nJN7LPW8AJWtYAoKQaDp+u4XShxgXhYcbHoxNTllCwETGQ8ag2jmDVsk8w/wCOp/C/hn+mWV/utpePH+D5wmF39NY6UakjUYR1Dn0YgRM5zQAAAMdfAA4AOAOArjkMNQ3vgm7UKtBR+m9QHFD5tpnDtpy+t2R20gK/OsmFtuDpaL5mVyiT5qdEVAvZci5ch5VoSGKbwlWTBr0RPoZT07av9lHfrXo6yLApWMugKpPM9SV1cDm65s/wkOHZBojoqiM+6GpMSj4FhtayNAUi5H3LfQBG2KWssFoSPuJdKyMLKtpuLi+e3jwFICUg7CSHsNVlYlKdizOTvKdq3KTsG8pQirsAG6vAB5FdhP490U4gfjxi+DedoqO4YftmKdKNulO26jiOv+2Ga/bftVNFXpHtVHrpLpRFJTpP3z77T469++fTx48e4LueE+NY6UKk7UniLP8A7rNf3X6//9k=/9j/4AAQSkZJRgABAQEAeAB4AAD/2wBDAAYEBQYFBAYGBQYHBwYIChAKCgkJChQODwwQFxQYGBcUFhYaHSUfGhsjHBYWICwgIyYnKSopGR8tMC0oMCUoKSj/2wBDAQcHBwoIChMKChMoGhYaKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCj/wAARCAD6APoDAREAAhEBAxEB/8QAHAAAAAcBAQAAAAAAAAAAAAAAAQIDBAUGBwAI/8QAPhAAAgEDAwIEBAQFAgUFAAMAAQIDAAQRBRIhBjETIkFRB2FxgRQykaEjQlKxwRXwFjNictEIJEPh8SZTgv/EABcBAQEBAQAAAAAAAAAAAAAAAAABAgT/xAAbEQEBAQEAAwEAAAAAAAAAAAAAARECEiExQf/aAAwDAQACEQMRAD8A2t0YoQpwT2qVzMV+N3UHgrDY2eoM0y58VEbgfp9K1yMRmnuJ5h40jyYHGSeKrWE8u2QAApOMdqGCsmT8h70TAJwMAZx249aKBy4c9vTNUC0zDCgmmmG7Ockjkj1PrUTAjcy5XP0ouCgHae4IomOJHhgIc55PHY0Uk5IXLMcUBQ27n96JYO2MYLebHtRBA7BcMx29sdxQJqwZRtIP+BQKpjHHc+xzigNGoAO/k+nPAoAYlee5oBiGeWySO9AJCgY5PHagFCADzj2GaA2N2TkjA/U0HMwbPPeiyBLDfkkj04FCl1cBMgn6URwYFGySR6D2oAeQDAxnHGKAhU4IbGc+tFwnwDj9aK7f8v2oNu+IHxNvJdXmt9EmKWSqArA/mPvxUxMZNe3Ml1dvNcMzSSEsxPOferJhht/OWyAPc0UfdgDcuM8n50AMCykZFARsngcY/egTcbjnJz9O9AB2kZGSQOcUCX8x83bntQCMruJ4B7D1oCyOGzxtJ9M80CAdg5UjFE0aFJrghLeNpHY4IRdx/QUNWCw6D6q1EZttEvirHAZ4ig/U4qw1b9H+CHVN3Mq6hJaWMJ5ZjJ4hA/7R3P3q3ET+pf8Ap/lWNm03XkkkA8qTW+3PHupP9qxopV78G+s7VSV0+OcAn/kzqSfscVvIKzqPTWu6XKE1LSL+Bhz5oDg/cd6lEZzGwLrtPqrA8frUCJfcw9gfegUjZsEAffNADyHt78UAjCjzDJxRcO5Pw3gwCGOVJQp8ZncMGOeNoxwMY96GCbQffFFcUXKjDDt2NEo+N3yyM5z3okKuqJgIzONoJyuMGi4QfGcqSfXBoYHJx659qKIRnnsfUGgJn/poJYoTIGLY+eDzQFlQK2G/KCTmgbspfO0qce/agPGcR7nHf9vnQFfBPlOc88Gg7uucc/M0Bd208YJJweKAYrea4kKQICRGW5IUYUZJ570DYqcknt3FE0VuVyDzj1oamOlulda6puvC0a0eZVIWSbtGn1Y1NNbX0x8ENH0qL8X1NdtqDoNxiQbIh8u+WpqL70Tc6fcxypouiRadbW8hhLFFXcB7Edz+tNFvEZxkmmgShbA9PlUA+Hgg/wBqDgmBkd6ArJuJBGR7VdEdqWgaVqMfh6hp9pcLj/5Ig2KaKJrvwW6S1EFoLaWwmPIe2fAz81ORTRm3UfwI1mzBbRL+K/ReyS/w3x/b+1Wexmev9O6xoE2zWdOubUDszr5T9G7H9auCJj2n3PPrUXTlGBB2kYx96GlQMjJJHuRRXBgDgk8DtRKH8w4OfYA0SUlIMsFXJ4oujHH8ufnRRGOSNoJNAeFC77F2jPucfvQFEqgY3nj/AKaCUY58wwq54AoCzOmVMke9QeRnGR7ZoEIF7pnaTk49KDpSSwQntQJsGKjgggZ9uDQc4OOe1Am2UCkHOR7dqA8t/cSW8MEkrGGEsUTPCk4zj9KJT3pzQtS6m1aPT9Jh8SVxlmJwqL/UfYURuuhfArR7f8NLrF1cXciKDJCrbI2b7c4+9NGtaRptrpdqltYW0VtAn5Y41wBUodvGjqUdQyn0YZqAIreOBFSFFRF7BQAKA1xcRwKplcJuOBn1NAR7y2ikWMzoZnGVQHJNAuQcD3oBKkD2FBy8jnvQFxnjjmg4rxwKBMqCBtPNA3vbCC+tngvYo54HGGSRQQR9DV0Y91n8DNOvFkuOmZmsrk5PgSNuiY98D1X+1XRhWu6DqWgX72er2j2069t/ZvmD2IoGG7jbnj1FFlB224PB+VClN4DYJHyAojmPGCck8cetCAxgjPp6UaAGKtx6+9ATAXO7nFBw8HHLN+goJhBuj2FeAcnmgNazW8U0vjweODGyqpYrsYjytx3x3oGa5LEEjH9XvQGlgmjjMmQq4HBPfPYgevagG5nhe3tkFuInQHxJQTmQntn0wKBKTlAeDx60DSY+U9zn+mgsnQvROr9Y3W2xi8KxV8SXUnCrjvj1Y/IUR6c6A6H03o6wMVgrSXMoBmuX/NIf8Djt/eiLfjJwO9ZBiOfmKDhktzQAzYBLZ8oyaDF+rOptVv8AUjNZL4tjA/lT+kr3wvqTQX/pi3Y+DqFxKXurmFWAaPaVzg4I/b0oHlxqV7penRTXFu93dPLsESYB2k8n7CgnradLq1WaIOFI/K42sPkRQCg3Kcd6Dgp3d6AdrGg5VxnjmgKWB8uQGxnFAUgKuSefSghuqNC0jXbAWGtxQyJKdsYc4YMf6T6GtDzR8S/hnqfSUz3NvuvNILYSZR5o+ezj/Pb6UGfLzyD/AJoFFySQVBHpQDJ5kGByPahAbWxn5+po0OF3D+XPtQJsNwOe+aAuygmMkebgHnHFALHYpJwSeGz2oGpOJWAI49BQEZlYAHkg4oARVOMvtBIJJ7AUAX6xxSOsUgmjViFcKRuHviiVfvhT8NZuqpk1LVFeHRkPlHZpznsP+n50qPS+mWVppdnFa2cEcFtGu1I41ChR8qyHVxK8cLPDD4kgGVQHBNAa0maaBJGTYzDJXOcUCy5JOaA2OMfoaArkheM7vlQNYNOtoWLJCgLHJwo5NApPKLaNpGRQB6j2oGmnRvcyNd3O/DkeErLhkWgklIdCyZOCRzxzQEeRxhdpUnncBkD5UCxXjJ7+tAlctMsIMLohz5mcZAH09aBQYdQwyAeaAuA7MAQxHH0oG1481nbGVInuWU5Kr+bHrgepoKB1u+o6jqlvBH05NevEBPBK0pQR4I4BHZj+1Bb9IS7lsFtNWtYwDGFYB/EXHqpJ7/WtQYx8VfhGbdZtV6Uh8gy81mpyR6koPb5UGKY4YkeYd88fbFAI5AC98c5oQBb+U9+9GnN5RgDgjOPWgAN3yMfWgAqc91/UUD2RSSRg9+49KCR6e0WfX9WS0icRwgb55WOFijH5nP0FBYNRi6dSR7HRNPmu0hOW1GaXaZMdwBwAP3oynE0XRYrFtV02wS4ECj8dp1wcsE7eJEf39qlFZ616ZttPu7Kbp9Zbi0vYzNCcgjHqoHuKsEp8LPh7P1PqjXerxywaXaviRSu1pWH8g+XuflQemIIY7S3SK3hVIo12pGoAAA7AClEL1N1RH0/oTalcwx+IACLaSQKx59Ppmshv0D1jH1ZbTubU27xkkAnKsuSMg/UUFluLlLaJXETyecKAg554zigXiubeRnSKeJ5FOGVXBIPsaBLULoWkIfw3kYsAqIOSTQJMbpm3oqlmwACeF9yfn+1A+Bx34oE5IY5P+YFbnPIzQKAckHuRQCAQOO1AL8r9KDhkZOT9M8UCcrxgAyYJzwD70CT3Itxm8kgi3fly+P7/AOKA9pskhEkZysnOfeg6RH8w3tgjAHtQRZ1uystSg0m5eRJ2UbHceV8fP3oJkBSAVII9xQFdSRwKDDvjN8L/AMSJte6chxcgFrm1QcSf9aj39x61YMH8Q+CkfhqpQncxBDH5H6VRwXJ/Ke1Am2QchuMYOaNFSAVznB9qAm8f10D2RmX8jDHP3oLbebtA6ej0m2LrfX6LcX7IMskf8kf6HcffIoG8yTadZxSTxCK3kRZUwSFfkruIJ78GhiS6Y1OS3160uZJFWO5bwZtxzuQ8bcfPNMZXvo2wsLnQ9R0q/maJNNv5Yo3bjCuMAHPzqA2jdUan0lF0/ZXcElxp9zE+5WVd/DE71IPPB7H2po1bSNXsdYthLp1ykyEcj+ZT817ioITrnoux6vs1gv5JYnjz4ckZ/Ln5etA+6N0BemdBttMina4WEFfFdQpIJJ7D60E5I4Vo9qnnsQO1A3k0yzeTxhCizZJ3qNpz9RQO449igMSxHGW5NAIwBtUAUAMORkfegMhG3jtQD8+fvQGXJz7UAHuRQA5YDI5FB0qCQA5yaCs2/SFit/Jd3AmvJ2bO64ctt5zwD2oLMilVAUDgcAelAJLbhgZz3oGN9HPIYmhtrWRw2czjt7Y+dA+h3mJS67W9gc0AvuLYANADpkZABHY85oPOnxy+Hx06Z+odGjC2jt/7qBRwjH+cY9D6/OrKMebcceHwfaqCYIyDgZ96GhHOFJI4/WjQpXnsaCz9J6fDqGvRC8OLO3Vri5PB/hqMkfc4H3oDT3UupapcXrKS9zISgDdhnAGPbsKC5aLLBHq9p01c6bbagPE23kpJYhmz5IySAAMj6nNGdRnT2lu3V9vaQQrJDHfCMFj5kAfufsMUFogu5H0jrLUYXK+Lq0aRse/lf/8AOKlFfudagvbnQpNQRmtILydCwPdCQcgMOMZFQanPoeiawBd9M6s9jeKPK1vKQp+RFA4septa6fuFtuqbRrmzx5b+BAdo927A+vsflQXfTr2z1O3W5025juIW/mjOR9KAZI914khaRNo4XdwT9KAl3b2+oWpjMoZWbOVfnI9sUCrXUNssUU8w3sQoJH5jQLvwQQC3NAKvuUPtK54waDg23v6UA7weBnNAIOBigMr+hoOjdZQdhBx3waAVG0Z7UBWfAOQSflQChyNxBAxQRutarb6bHALi9trSW4kEcJnGd7ewFA/j8QEK/IA/MBjmgWDDBB7igj9dupLTTbiaHZ4oQ7A7bQW9ATVgwXSNV6onl8azW6t45pWdxHIxWA/zNtz7A8Glg2S1u7fX+nt0J/H2c4MMhmQoW9GBUjj60g8sfEHpebpDqi4sHLG2Y77eQ486E8fcdvtVFekGW4UfegKVAAKgnFGhuDzxQXbpDTZF6a13UnUqrCOzQ5wGZmXIJ+lE0ppkEK6nJcRWcTW9hA08iKcjcowpye/mxQ0+6VRbC/jvLm48L8LG9y8pIOXxkDnuSTipqHXQMng3es9S3fhn8DbvcZI5Mr/lH700dc3Dad8NtPs4nU6jeXD6nMCwBRF5XOfU8YHrTNJFF1X8RawW1jc4GxTKNrZB385yPkBTFw1stSu7Ni9tPLGSQfK5Aphi8J8UNUm6fn0u72yvJ5fGbuF/39aYYtGgadp9/axXnRetzaXqnhqZI3bEcj4547Ak/X6UxFisPiXe6NMdO65057eQAr+LhUlHHbOPX07UwWXpQ6BqMo1LpgW0sioVI8Qgxk+684qC028M5890Y3kHKbUwF+lA4LDOzu2M4FAOG3DaoI9cntQdJxzQEyR259f/AKoGl5fSQRFo7ZpB/MhYIR9zxQdayyXKb7gqox5Yo2yB9WHc0DPUIWnhWKxkuYFRs5gcKWbPY59KBkx6isVeSGW31JNwHhyOUkA+o8v9qCfjkMo/LJFKqBmRvSgc2swnRyFcYODuXGfpQMtRsLK8vYJL+wjuGiUtHK6hghz6Z7H6UEmCsig84I9RigiruC9t0DaaVmIIHhTOQMeuGwT9qCJ1ywv9T0U29xFFiaVBJGHz5M5ODgYPY/arKJPTtLW1t44i7SKq48w8x+ZPrTRJoipGFQAAdgKgzX47dMJrXSrXkUe6807MykDkp/MP8/aro80FQyZ+tUJ7hvH0x270XQ7KGtXvIk0T4c9P2bIhkvpnvJVfjIxhf7qftRDXpu0/1DpzXltUlkvmWMBI+2zdnn64oYa6yX0XTm0i4jQ3t6wmuV53xov5UPpyeeKyLbpFtZ6Xpmn6TqNq7/ic6pqQRR/DVf8Alq2fTOP0FXBnXU+ox32o3lzeW+JrxlMXHKR9wfbJ/tVWK5f3AnaAjafCTwwcY4BOM/qKKSjA4Dg8j37UHZKkE5P0olSFlcLDdJPbTNBOigjxOVZu3+80Rbbnrq9l0t9I6isRd2rgKpPlZMdyre9An07oupoh1zo2+lea2fMlr+WZFx7ZwwqWDVug/ihDq7R6b1EPwmpMNokPlVj8xng1BqEUe1EAJOMDOc5oDSxq6YYeuaAJF4oCBUQ7mJ45zQHYB14wR86AVjBXyjge1AEcRTHlA9hQE8kbgEohJ5yQM0ETHNqMOr3IZQ9tIMQyEjKt7D3FBLqywRPJKTuxlj3zQI3Ut14e+yhWRj28Q7RjH60EfpF3rU/jLqFrHbS4/hqpJXH19aCRa8jgiVr1xGwXzYyf99qA9tc29/aRXFnKs1vINyOO2KByoxwe9AYocHGKBvdwLcWzxSLuR1KuD6gjBoPHXWujt071Nf6YSSkUnkJ4yp5H7f2rQgWAA3Y+1An4j/1t+tBrHxKuYS+gx24LRx6ZFtI/lz60FY0+/v8ASphNpd68EpXY5AGNvzFF1YOirZbzVrvX9dkNxZWH8eeaY5Lyj8qj7kcVlETqOqXd/HrPUNzcNE16Tbwxf1JkEgD2AA/etBte9R2Oq2cv+p6XHJfBFjgmjkMaRgAAEqO5o1FWfbgjsR8+9AlI5CgEggeoNAq0iug8uD7g80KKmCcZ7fPmjJzJfT/hWtjJvhOPK/OOe49u9A96X1W90/VrRtNkkSfxQF8I5yScdvX6UGidSLpfVFzcvbRiy6kgZBGysFW7B9T7HHNSjU+o9S1iz0e2uNLmX8RYxJ+KgYeVwVGTn5d6gjug/iU3UOt/6TewQpP59skL5B29x/8AYoNHPB78Ggb2l3bXO78PKsoyVyvIBHBFAoSkbfyhn4GfWgTnmWFN7ybAvc4Jz9hQRdx1dp0S3Dw+JJHbDdPIUZUjX3yRz9Bmrgzbqb4x9Oxho4bB751O5HPkXPsc80wQHT/xrJ1IHUbGKO0kdRiBiAgz+YjnsPpTKN/tLy3vLOK5t5klt5F3LKhyCPemAYLuK5XMDEj1OCP71ArGWLMPT0oIbU7h11u2t49OllWWNm/FIRsjI4AI/egfQ2ktpbww2XgxoDl9wJ49cUCHUGv2GixM13Mkcm0squwUH5/SrgxDW/jFcXOteHb3otrKEEiRISRM3zGc49v1qDT+gfiBpvV7y2unxTxywRhz4ozuHbOR2+9Bmf8A6kNIEWpaZqiooEqtBIR6kHI/atfRjDEt3AKjgVQjug9j+lQWh72e/htTOzyeCnhHPomeMYoJvQum7vVD47K9jpsQBkvZ5NoAHcgUAa7rKamE0Lp9Xh0G1OZZTwZSO8jn9cCsivdS38F9cJDZIY7G2URxKe5x/MT7nNaEKrENwAFPPlosFwS2cd/cc0UlIm3JOeKDo2LH+UA0SjgDk98URzPiJ2449e/NAbS7v8PdpKkpikQ5WQLkqccGgmYNQmXWLeQLG9wVRQVPlcj+Yn3xQa98OviAjz3WjdXSpFdliEuJCNjDtsJ7enepRdel+kdL0rqOTVdIsoYklV1dixO3nunpg9jUCnU3WMeka5b2EUcl3JInmigQs6ZPlJAHY8+vpQP9O1m3nthNo0cTwM2JDwoVj6H5gd6CbhtUiVn8TcXO4ktkZ+We1BAf8Z6fZ2uqXWpyxQrbStGseQzMB2IA961B59+IHXmodXal+HsPFh04HbHCo25+bY/zQWv4f/CCxvII73qC8iuXYb1tYZeF9txHf6U3BatX+DvSl86x6cr2dwjbnEUmcj6Enj6U8hLdJdEX/SmowJp2tTT6Oc+La3HO0442+3NBf1LmRUjjQAfmc+nyHvWQockYyQcY3CgaabaPZxGNnaUFi3mPb6f+KA2q3RstNurnBxDE0mPfCk1YPMemaP1L8RtYN9fJPc2aMUaVmCKg54H0z6VRYendf6Z6T1W56a6j6fgfwJyguhGJmPzbIzjHtSjTn0zSunbi01fSkt9Os5GAmWNCDOGxtXb6HnNZEZ8etOF90DPKFy1rKk3zAzg/3rXI8u7zvOTg4zVoTLDJ81QWDTb2SwuvFgcrkbXwM5H0PFGqsjpd6+kcT61Nc2ieb8OikFc/9PA+WfSjKA1nWBzpFlZ/hLWM4KH8zsPVj6mghN4IyQRk5NGo5BkFmyAfSgVjChdpGO/FAXYpOHLBe/FAQqoBJbA9sUBGxgtgEj/eaCf6DGjt1TZf8RNGumKS7mQZQkDIB+WaMrf8Ub/ovV7V20JIYL62K4khhCLOCcEcAdu9BmCuEQvxvyFUg42+v+/rQaj0zax/EXRY9Nns0t9TtM+BqCKAjEclXA98jn+1Si7Cz6u6O0tLjTrxLu2tQJJrDwcKE/m2M2SfeoLrpupDV9Mh1OytUS2vIN8m4BZQf6T7+vPpj50GfdK9L6rJqk1y1y0elRDKRqdjHHoyDhjx39e9BZr7fagW0j3kul3iETRqHkeF8ZBUjkZIxjtk5rQ86dW6r+O1OcW0UtvaRsY4oWfLKBxz7k/5NA46P6X1rqS6WPS7V9v88rAqi/f3oN46X6C1DSotkus+BIwKl8hn2+3PapROXPT2t20bPY6kJ5UGYmbIfIHGW5z68VBI6DrzzWSrrAjtrwFUbDja5OBlfuaCbluJLeNwIpLiVF3bVXAP0Pv8qBxLO8cYcW7vnuqkAigNFKs8CyxlwG/lcYI+1A31ayF/pt1auSFmiaM/LIxVgwfoO413o3qqfSLyUSwodogAyZVGcbPTPr71aNDvendJ6wtbu7Fi1lezK0bS4VZMjtnFZE0bC5u9Jh0qRAr2yw4uWx59vBI44PegN1tpbap0lqOk2sipLPB4aFsnHbBNOR5A1exFhqFxbeKkngyMhdOxIPcVuhiZFz/zBUEwcKvYnP6fWi0+6chjn6h062uATFLcRrIMnzAsO9EehNR+GvTV3GUh0+O2YsGaWHIf9amjIfib0no3S0VtFY3M000zMzLJtLKvvkenyx96oz0rwNjA8cj2osFLbVAbOc9jRQiXOAwxnj3oBlAxwDj37UDY+vHOQeTQBIdqjcPMfnQwJclWyBgCjJBFeefw4VaVycBUGST2wAKD0L8H9C1rSIILjWLSCytY1lZASVnlL4PI/wD8+vvUo1uwbxI5GkjdVc7isvOBjtj2qBWKFZiQ8CJCB5FHYj5jHFArDbQ20ey3RY1HOAOPsKCH1u61CPSLt9MtlXUHUrbCbJBbPdtvYetXR5T1y2udD6lni1ErJdJLvlK4wWOCePvVgsV/8Sr67UW1vA0NiowIonMe4+7FeT9ARQRmodWa9EYpPBhs1Tygw26rk9xknkn70EjonxZ17TXjAeKTkZ3L+YZ7N8vpSjX+lOpNM6umgkMG3EgBV1DYbG4kewz2NZGkC43CP8MPFBONysMAD50DaHVH8S6N1a+BaxMUjd280pA5wPb296DrXWLK9WNoJdtwybxDKPDcAnHIoJBifTBzzmgaz2UFzPFNNbwvLCcxuyglT7igdRRKg8qAZ5JAAzQEnuYoHiSWQIZW2ID/ADH2H6UERr12BY6hueIQJaO7SK/nHfnHtx3pyPGWoN4jynuCfU963RF+DL/UtQWTkjaWY/8ATnHFGql+j1VerdJY8r+KiJz/ANwoy9C/EjqSbpbRY723RJC8ojIcZ4IJ/wAVkecer9en1+9FzeLCCq4URjgDP7mtLhteadBY2kMczyHUpcO0YxtiUjgH/q9celAiLy1kjCX1ruyMLNGdrj0+h+lE0+t+kNQltJ7yKS3jgiTxUFw/hySp7qp70NV6YEBgWUNjBoaKeAODnHrRoVgDnBP0ozpxZ2f4y5trVeGuJFiBPpk4zQep9C0LTembS30fQbWP8ZsDyTugZgf6ix9fYZpbgmbXSmXULaa6kMzpltzcjJ//AGpaLCY1CDsF74PrUCgHY0HbSx7Z96BGUfxB2xjtQZ11t0Tb6jNfyw2wM18gV5AcBdpzyPnV0Yp1F0o/TEczXjXaTOQYpIk3QlT3B9Rj0zVl0VKbVppImheUSwbsgFfXHc0De0tri/ujFYQSSyfmKopPHqaDV/g9p+padr/gkSRTzKu0kZRlPLYPbOPf2pg9GWzRCMJAFxH5do4wayKX1z/G0CdzqLWRkiaTxQBLudclQvovbv3oMU/4Z67uwnUAt3u1Zw42yhmx3/Ln8v0oN86L1d00i3i1UiGQIocNnEbnkqT2xgiguEbI4DIysp7EHNAZnxQQ/Usksej3EsCl5EUthR5sY52/Mjigr6Qrp3R15LqEcIlmgdpFGAsY2navPJApyPJtwd8rnGBuJz6Gt0MzGSTyf0qCwSKA5ZsAjnn2otTXQYj/AOMNIDqCrXUZwf8AuGDRG6fF6Gyfo6+ub0CR4EPgIScLIeAcfc1keatN0661a+S3sYTPKzAbV9B7/StLrQ/iXp9pYLp8elWsUM11AzXMqt53I7g7j244oiB6W6Tn6j2TeAy2FspTeB+Z+/8AmgtnWlvpdl1Dp1pq07Ja20GFQpuDHHAwPf39KDHriVTKSPOCeBnHHtQGsrG5v5pfwcTOIlMjgEeVfck0XRIreS7uUigRpJXOEVe5PtRE/wBJ9HaxqvUcdhNFJp0lviaSWVcMgzxgdySeBipo9T6O8NppUJ1K4iW5KgSvIyqxb5jPH0paJm1NvKivE6Mp7MpyP1FQLRTwy58F0cjuAckfagOTtO3+Y8igMWCIWbOPlzQNhNBOWEbq5Q+YKc4+tAD7JEZgQfXj0oI/VtIttXsZLW5hRopByCP/ADVlGRa78Erae63aXK1tG3LAncM/Kmh10l8IZdBv4rxtTE0yggJsyoz6/P0po0zSNKEMdo9xGnjxuzkqMAEgjj7GmialjWQMgyCRyQcGoITqHT7q/a30+G2jFmwLSzl8GPBGFA9c5NBPRwJDbpHCipEi4CjtigqfWltqCaG8WhNbxyzOBIs8W8FcY4+dWQQ/wtuZdIGqadrknhy2u2QyOSEZOeRngY+XvTBZZevOmhC8janbqiZ53Zzj2FMFcs+sh1ZqsFrp8UkGkrlpbh+DNzhVX5Z5NQTfXyWUXSV2t+wW3EZ5I4HHt61eYPI0mA5C9snFaoLsPv8AvUEk5JcA8cZG480WnOlXX4PVLO4yQ0cyP244Yf8AiiPUfUump1B0/c2O8xfi4v8AmL3UcGpgw/SujNX0Trj8PpckimOMvHO/kEg9Rjs3PpV0aFq/Qqa1ZJ/qcrverEqNOwGM+uMfemiVtrKbQdMNjp9rvtkhPht6mU5yT8u1BkvXg1qXUtOvddgRY1R3j2YHiMvZSD27CgzSCyuNQ1KK0giL3Mz4VAOc/wDignoNNOnaHeiW8hgkku/Al2+Ziqgn09M0ETp0qpqSmGKOdFcEeLwMfPHag3JLuCRtPmQWsDhNphtVAcn1w3BPFSwDdWGpX1/OYdOtbbSrlQ80szHdn0GR24/c1AbWemdatLbTJdGvJIJypDQwMV3exwOPatSz9Ei/R+txy2mr3evyHV4miWIDhGwwyGA7nGRS2YNZAUBWYDdjGayEvxMYB3nYu4KCfU+woG93c2enWs1xcPFDCp8zEgDPzq4GGgz22saS1zZSZhkdsFePXt86YHWmySeLNDMYikZ4YNlvvUD+VARxQJqgwRQHUAAe2O1AWOFRM8mDlgB37fagb6reXFt4ItLZJnZsuWfaI0Hdjwcn2FAz0nWX1i4u4xY3VpFbv4eZ1x4vGdy/KgkriN2aMRlQoOW3DOR/5qwYr1P1tp2pdS3WnanKkGh24kRl2eaYgcb/AFxnnAqiv9Jno0dRLJPbtdQtkNPIALaMnODsPPpSjbdK0DTbWQXui+Gsco3BU5hPP5gPT7VkU74t6PZHpq/1N5ZZbwrtRnmOwDPOFJwPsK1xR5ybudw788VaC5X2WoJRULSBpAe5PA/aiinAZnHck4A70THq/Qr23/4Y0u4lmCpLBGA7epxjH60Du+WGOBvFlFuWOFcYyCfbPrUojri6k06xX8PFNfBUJ3ltzM3scVBjfVvVXVNit5dapNDZGQGK3shjeAe7YHIwAOT3zVggNTiu+orrR4p7m+upJFR7h3TPhggDaoBwRjnPH5hV0af0xotnoD3l5dWdrY2YjGLhwPEHoef996CC6m0HpuPpk3Wny2s9sJPHJ3AeI2D39T37UGU9QTDULuGPSLPwIyoVIYk2lj6/X70G2/DPp0hVudRuBLcwxhRGkeEjB9M+p96DSLprVHiieaAE+YxHkke4H1qUOIBawL4uAuc8nvj71AwjRtQ1eO78QNp9odyLju/qT8uf70Gb6r8SpLzryy0vp+4NxYSSCEswI2u2Rn3OOD9qC4dVamen9NlaC7tUaIFvCmnHiy4HJXJxnOeDVwed+rOvLnqSyWO4jZSru/kc7ck+30GKosXw2+KmqaDJDY3jR3OmqNoRhtZAP6SP7Ggtmt63qbTJ1XLazJpslwBFblypEOAA7L2OWANS+xrnR2vW3UmjJeWp8wJSRf6WHeoJdSPMCRmgMq8DmgBpNsgUIxBGSccD70DczmS8MDWoe28MN4+f588rj980CktuJZYpFdlKZ4B4OfegQ1hpIrVjbsRMBhBj8x9qsHnX/hm36y1O/u9V1ddPmS6aD8OkQdyxOSe4OMmqLUvwQsYY4Xjv7m4YEEhwFyMY7fXB5pRbvhp0jqfSMV7b6jqZvLGQAwxAEBDk54PuD6VkVb49a5DBpiaNaeF/FIaQDumOwpzMGDEZQZ5+VboR8In1I+9QWDY6gFn7jjHpQhtJEFbAGBnijT0P8H7qPVOh47a42yNaymPBOcDupoykep+m73V7g/8Av2itQowvJIx6j5/OpRjfUWrax051RPY6LqFy8YACkebO4Z7HjNWCY0ToW2utJbqPreW5na4O4R78cehY9+fQVKLX05p1ro97awC4kX8VFmJLeEKdoyfOxJPbHbHYVAz0rqKPWNauri9t1ktJgILYgEiNFJ/Op9STmrBBdeaFCo0y3jt444DI3jLE204Y5DD+9UPPhv0NaRtPq99mSLOy22nOfdh75oNC0vT7m1uJGvGiii3AW8UDbQAeDu9zUohLlhouqap1VciF4I1FtbxSthtobBIPuTn7VBJ2vUth1TYk2ULi9iALwyKQYz6Z9CM0Ft060/DWEcDHe2Mucdye9BFW3SekWt3LPb2cUTsd2UGCG9x7VYMzufhzdX/WmoXj+BPpx3I7XZMmXYckc8EVRKaP8I+nXikLQuxOQSTnBzj6UEjonw90XSrq3S3s7dplJcl1EhGDx396lFx1TQ4NVjaC7UNCU2lAO/8AvNWDCLp9X+E/WgWImXSp2LRq7eSRT3B9iP8AFSjd9P1+21TRodVsMS2rLmTbyUGOePXFQSltcLcW0c1vh4mXcjDswoDLdRm4FvISsgXeTghDzjAPbPyzmgVFxCzuiOC0WN3sM+5oDqySJmNg3rx7UFb60tNUubGJdFdEvhIdryflUFSM49TVgyTQenJemOorf/U4H1Fpp1edAh/hOQTuQ9375JA4q0bnbPBcxxT20wkjKkqYzlT9ayGWu38um2MbLEJ7iRtoUds+/wAgBzQeW/iHqi6j1PdzeL44HkL9txHtWhVUOVyvHNB2F9zQT8hUAhAdp5FCG0mSAzE4HGDRppvwL1bwOpJbEsFiuYyVX3deR98Zoy2ZtRgmjkSRZocEp51K7se3vUow/rfpFE124mVpfD4mk2MWdCc4A+VWCH1281/UmFnpklzPYRFBEG8uGC4yQfcn9alGgaJo95rRsbi53WaxwrHOm7BjYcHnvz/moJaw07pXSI5IW1K0CQnDhpAWB9R796CudY62msTRW+gadI8KnDXMkLLv9MA8HGOKC3dAXF1dRfh75f41moi4G0AdwcfTj7UFhv7RjqMBV5AJFZHkR8FRjIx6CgpXVNjJ1JqNn07p26CztSJLlpIydyj2J+fGaC+afplrazqLa3SKNIggx3IHYUEsBk4wQc4oK11L1z070/M9rql6wuVA3QopLcjNBDwfFboqeSO2W7kQNxuaEhQfnQLt8TuireVoV1UeXnckTFT9DigHRuv+mbu9ZV1W3Nyc4IRlVl9O47/KgtU+s6baw+JcX1umRkAuM/p3oK/1t0rYdX6cqXKESqN8Ug/Mp9P1qwZ702mo9GdUTWJsmOn3EY8CAORGXJAwScjJ5q0bJDNLb6YklxbKsgA3wwndg9sDtWQN3aw3ZKTwLLEQOGORn6ehoG1vYAw3FikRt7JSuH3Hc/GSc5P0oHn4aO2uGuYyiose044wBQIm6F1dwfh5ARs8R8L2BHGfnQHv9PS4PjxrGLtFKxysm4qD3oCxboIIo7e1jhQHzAYUJ8wP8VYM56j1ktaal1BMrS2sAaK1OQDD6eUepY9yfQVR5zv7hrmaSaRtzyHJY0DcE4BPIPb5UBwOO4oJYzFvzEYHAH9XvQhNZN7AEgDOSDRo/wBA1SXRdVtNQgb/AJUgfBHcZ/8AGaGPVlhPbarZ2t5CEeORBKje2RUrI1zYxTBhMinIwcjvUEcugWkO4AMisMEA8N69u3yoERrOhWNxNYy6hapcxAeJHM+D8u9ASLStLlm/EWdpZyxy+Z3RQ3I5B44oJKTT4blFWSNBEOeBg5+goFYbOK1TKhIxnIbGMH50Cpcyo6AMrIcM2OD68Ggb6Lbbllu5Cd88hYBu6rztWglSNkfm4P70Gaat8Rba96w0vp3R2mhufxyi4kO3YyDOV9+f8VYMw+P0cP8Ax4JVuEKzW8bEr5tuMj0+lUZ7Y2X4288GK+towRlZXYqv9uKCQi6YmbT2u11GzaJWKnYxbBB49KCFnhubdiwL+U8OhP60ElpXUFxY6nDdXQF0qYbZKxwT9vWg3npb42aHcmC11C3uLSQjEkpIdQfr3xUondP6x6e6tv7e101hczRzrNtaFiFC/wAxPYHtUF+lj8bYCTgMG59cUC4OBQQOo2eoXepFTeL/AKYQN1sEwWx6Fu+DQLX2kw3Ok3Vjas9qJ48Exd1PHb9KCE6R0G86Ut7mK71KK4gklM7TyKRIBjtjtjj96AOreudJsrMJbXksk8jBCbVdzRjONxBHP/3QQ9x1jcWGkERWWqXdpMPCt7x4wfFOOWPbA+fAqwZr8TJ9Qbp2ymvEjsrSTEVvawyHz45Lv6E4wPqaoyl8g91OKDlYEc8mgKW5PH7UE80f8PPHl7gDFAZkUjawUIQG8w5ouknAUbl9Dg59KK1X4Z9XXFvo8mlRXax3KHfBG8Rk3qe6jHOc54+dMZO7jr/qK8vWtba4tYu38TwvDOMc8N60wPLbrW10PS7pnvrnUtbAKobgBUUk9jg8f/lMC2rydMdRSaRqWoLEbx4UefwxkL2BVvvn9Klgv3Tp0lPxFno6wJ4IVmEOMEHsf2xUD2e4ks7n+NGDaCMu8q8lCMcEfPNA6tW/EwrMybEYZUHnI9Cf/FAzu7G4LXTWs38SRNqhs4Bz3z9KCO6x07UNT6altNMvEs7xkC7nPlI9R2/egwbrDT+r+kupLCeK9nu3KBYGRy+QvdWFWCU6avtA6h1iKDqLRhpmpvkxz2p8JGb3z7k557VRX77TdHteuPBut401CAouyXGcdvmASaC069030brYaay/CwPFwWspRErfUN7UGZX2hWSiY6ZrMc0CvhUlBUk/UcGgiLq2mtG8F54yDwfDfIoGkrRsSZXwOB2zmgsvw06XHVfUcFvI22xQ753Ze4H8v3OBUo9a6XodjpltHbabDHZIhVsQqBuA9DxznFQTQUe5oDYGMnn7UEbpV3JqDyz+BJFbBtsXiDBf/qx6CgDXL42cSRwGM3UzBQrHGFzy32oG2i2kKTSI80lzMow0rqQoyew+3tQO59KtJJRI9rEzgg7igz3z/egZ6paJdGGwW4eBXy7pGeXUdwT6A5qwebPjJrcOr9TvbWZQ2Onr+Gi2nIJHcj7+vyqigOuRk+vtxQAqEk4BU0ABj7j96CzzKxYD0GeM0CQG3OMAjkfOgbSZwzE4PJyfWi6caTdzaffW95akrPFIrLg/tRHpGzs9C6t0W31FrO3Y43MrcbH9c/eloZ6v0JpWoKlrHHBbScSFEHYc5Pz71NDXUoJrK1g0dvw9qsspW3nXaN6KMrHnH5ieSfan0U3Rr1uidaRbiwk8BUSS6naQkjc3ZcHaRnn70wbja6lZX+nw3NvMksM+FXnPJ9DUCeoXj2hSG2t2km7op4U/f/FAvHaNePb3N0jRzRA7VD8Akc9u/FAvcxnawZQ3HYtjJoKfDFAdeub6Vo1dSULIBtTbgYOfU8jNWUVvrm5ih0m1urixhlsI5HJliOwR5/LkkHHJPamjHdQ0HWdemlutN0+YWBYtC0rHDhjwVz3zWgx1n4e9U6QE8XT5Zd//APR5se9XBXbjS9S0zAvbO5tyWKAOhG4/KpQ3ZHXO5JFK98qRUGhfCbph77Uvx91pv463wVjR0LR7s483796WjW7rTrXpHWrSW2YK7lmXTbaIFpCRjjHOOSeeBipaNLtXuIre3R43lnkGXYADZnnmoH6Dkbzn6UDGWe9a/hKG3jsW8riQMJS3svp86B6zgMQmDtGT8qDNb6XUpOoPx72tzOkjFYowOduDwDjj70Gg6Wsq2KNeAJKRuKk52fIn5DvVkENrvW+iaSAsl0txI2Asdud5Yk4A4pgzv4l9ST6JZSXbyyprWpw+FFa5G21gz5icfzH3pgwCSQlh688+tUEwjjngZ7UHAHuWAHpn+1AXj5frQWXOGBZcKSe3c/rQIyAtnI27eBj/ADQIMAuH8vHBB9DQwVpPLjOckEZ/ahi9/Czqj/S9VhtLm6aG1uZFUsT5VOfX5Gpg9GiNJArxsrxsv1BHypYGF7pljeG3kvLZSlqzNGGxhSRjP6GoG1yLUWiWc2nSPA4KJGItyYHYHHarop3wu0jWYNUvzriNBp8ErraRMANxJ/N7nA7ZqDUHgSQLvAbacjI7H3oOuIFuYzGS68jJRyp4+lA0m0yDwGjiTw3bzBwTuDe+TQVbV+mLmW1NtbSok9weZiC2zPLEZ+/FBM6Xo40/TYdL8Jr21G4vJcuCck55HbFWUKQ/h4tR/DTz2o8TK21qmMgKOf8AfpmrokljG1i5BHI57D5VNorut9Lab1LA638W6H8sboNrqQckq3pntV0RWsfD6K7SGC3vTFahQJY2iVmkI9d+Mimie0Hp2DQ7AQacio3JZgqjcT3zxk1KHGldPWtnqMupS5uNTmGGnk5KjGNqf0r8qgmkhVGcquGblm96BDUZZYLGVrdN8+MIvux7UGKTdXdbaRrFvbaxbWN4d58BmwCjHPORycLx2q4LNe9S9TdN6I13qkWmzSXdwBCGlO4hiMKAB2A9ag0WySQwpLLtMjDcQBhVz6CgoHxF17XbnUYunulgsUsu4TTvjIUAEhR+x4qwZwtkOi7651PXJobm4tohHbQhdgecjnaPZeOfeqMy1vWLvWNQlvb+ZpJpWyT2A9gB6Cgjy5AO4A5oAGRgBR39aA7Z8MkFtxPY0AbV9UGfpQWhj5TkBQGxuBoEGG1iQCyHvj1oELgSkK6oRnIBIxzRdJ28Q3+fHiAds96LoH3AF1wCfyijNbF8JviI1rbQ6Pq/iSopxFOx5Uf0n3qUbWQk8II2SRyDPuCDUHMpSIiJQSBwDwKAgTxApnEbyIQ+APyn0+9A5B3AgfmoEWgcb3VlMpGFYjt+negSs7zxH/C3RWO9UElM8SAHG5fl/agNdXcEbJAZ1WadvDQDJO7Gf7c0ED1dqWv2enzw6Rb24nZfJd3EwREHqxyMZHzOKBbT7H8PZWTK5uZ9o3Xm1SzEry5PsT7UFF+JnUezSZ9LttRs2km2m5KSFWXDZI491AyBzVwK6J8T7CRtPjee0tbaGAtdNISdoXgLEo5JJxyfSmC6aF1fo2vELZXDJOxwkMybHYe4HtUFiJWJd8rKqjuTQcZV8SNI0dy43BlGVA+ZoBniE0RU7tp77Tg5zQUv4hNrU2tdNWOhylPEnaS5UHGYlAzn5cn74oHGt6l0z07k6nJC123HhKPFlbPptGTj9q0Kx0XMvU+ty6vqQtpWlZo4LOdGDWsak8Aflycgk+v2qC8a1q8OnaXLPOz2kCIWkZ+CqjgYx6n0xTBkmp9Sabp0KdRyI5vJkaGw08MVKIDw8jA557896QY1q2o3eqXr3N7O8skjnlnzgn5e1UMCGV/MOM0BJFOVwfX0oFtgZTjkg8UBtpOeO1B3hg85FBZXVMM+VJAA2+h96BO4IMJ/p7qvuKBKacmOKB5CYYx5UzgDPfHzoGwD5OApJHAHrQEAk8NWdNpx+XdkA0AIGhkGWOQcgg8UGw/DP4kmwhi07WCTZqAiSbstGc4+pFKNvs5o7q2Sa3kWaJxkOp4NZDOHUh/qL2k8LW78eG7kbZv+0+/yoEZp7fUpX/BXpgvYZTCSRtO7vtwe/vQdY6jeyatPp91FEPw8aSNMoYbi2cADt6Z70DS60KW7luJdV1JniJzBtURG2b0KN7+/vQKSWUWnLLqN3cSLP4ex5Y8jxiPykr23+nzzigpXUPVOu6Vqmmf8UWttb9OXDqkjRnfI3H849uRkDOKC0axLFr+nLB0rrUMM0bqCIGGGX1AH09qsGc9UfBiTV9Vhu9Pu5oPGLNeG6bczN7jHvVEr058Gre3sLeDVrmOdo3LmSFNjEH+XdntQXO51XQOl5YrCKGWa8SMYS3tzMyLjjJHb9alDqz1S5ktJ7nVdLmSVDiOONfEMiE4Xy+h9xUDm11CaTxEOn3VmpHFxKFCr9s5GPmKAus6jb9M6RJf3c88yxpjcxL7uM5OO3HrQVTSupoOuYdZMTSpptriNFtXKXDA/Pjhs9h2xQOJ7Xpnpa2S91WK2swqjbGw3ysfcnuxrQsGmapYvpwvra1FtDL52Mi+Gx49sZoMb+LXV0t+jWl3OYLGTO2zjx4h2nyszHsG4/Sgxt5ZJmEsjl3PB3GgSlyXBxkDnNADseB2PsaA8SoXQyFgmQCV70B5R/EIjYmPJxnvigEKcYDfrQF2/X9aCwqC7l2zwfT/FAJJ5747E5oGTqZArKOfccftQHZWwmOD23Z4NAEkTEBmwR7g5AoG7KSSE5HyFAMTyQsMHa/cEcEc5oL58P+v7rppdryPNAXx+GfsQe7Z9D2/Wg3zSdX0fqzT08F433eYwscOpHt9PcVkQPW632mX9vfWdrbXiRgrIdu2eHIwGD57+nIoKdc/ELVdC0u5afp27SUtta5vJMMzk+UDjzYHtQWDpj4gxXmif/wAitXZkGZzFGW8MehZO+PmM0Fibr/poWQmF6xXA2xmFg59sKRk0C2nQP1KFvdb0vwIUJNtDKcsVP8zD0Jx2oJDTNA0vR5p7qzs44pJOXkUc/SgNfa/pNvbF5L2JgTsCo2WJzjGKA1jcNcxOF/m/I0zbt4+gxgenNA5s7CCxWWYQxpNLgyMiY3nt2oHajcuexAoEL1C1uyFkVHO1ixHb17/KgwT4rdXWep6oul2OpywaTYqVLxDyySDjaM9x6Z+tWDPdB1TW7Wa9sumpGlursqMQRlpXwd3BA4571RcdN0i41G7h/wBSmNxqdkwn1O6u5/4cAXlYgcnngE/pQNvih8S211obHRyYbWInfJG/Ex9MD2+tBmNzcTXTtJcSSSSHH5jngDAH0oEdxbg5A9wKAzPwO+fegSLfLJoFoR5fUfegXOcHGAT8qAM+XaBzQCCwGDuyPlQWJpV37Q5TIweM7u/f9qA9vNYpFML2KaR8YiaJgAh55PvQRvnYoqA+MThcDnPai4PKWQlH3K6tggjnPaiEmz4ZznBPfFAVWG0AZDH1z2HzoE7lhv8AJIHI/mGRQI8AEeuOMGgndN6pu7V4RJLKY4WDLhypXj0oNL6d+MMS4ttetDdQgDNwAPEwPRh2NZGkabrvTXVZiexvba5aI+ILWZQG3Y4IDdvtQScvTdjK8chtFjkQ+VlYgqPXGKA17daV07apJrV9CsZbELTgbu3YY78UEHf9evJ4K9P6JqGoiR1XxjCUjAJ5OT3NBM9YdSWPTenwy3t7bWbSuBunUthfUhRyT+1BA2vXnS/jGdeo9LnIHljeLwSCe5zgmgejrOz1S3kGhazoaXYGAJ5Sw3e38uaCsJfX02rPD1XfXtvcCXdBJGjLbOO+EK88Y7nIoLB1H1Bb6WkN1ddSQ29io/5MZEjzt7DGTjj2FXNGUfEH4wRaxCtnp2kwGGM7llvBvIOO4XOAe/fNMwZbqusalfLBHfzSvFH+SIgKo+igYqiwWfWV30rpp03p6exJnUPJexQnxuR+Ulu2PkKCrT6jcSiTxZnbxCWcFidxPJJ96BBDlQ35fbFAbahBHJIGO+KAIwg5YnB455oDkKcbW7UAOowSMjOORQcCVXPp+9AqDkHcDmgMNpHPcUBTuzQWCJXcFvKR2Y0CMiqjnz4UcH/6oG8gKluwxyAfSjQ6ylEJBJfv37/OiYQMjbjkZXOSP/FEELAEkNn1waBCXdjORnPoc80CZeTb5wQe2BQAm4y7jlhjvQcWO3cW4GB7ZpgGC5a3uUeNyGQ5GCR+45pgt+l/EzqLTgxj1O5Zc4CSOXCj70wOE+Jd/Pq0V7qVvb3bISAWUBhnuc+/2pgvkHx0soLaNIdKkEiqR5yDg47cYpgresfELSNc1n8VrFtAw2ZBiiywwcgeb14x2xTBYNA13ozUo/GOqWVizDc1nf6crIh/7wOf1rOURvVupdE6ncpFeakiSWsZdbjSLfw1Zs+VVyMHA75xWsFDHU0idTJdf65rT28YKpPvHjKp9Bk49qYK/rGpXF/qU9zPdyzyyMSJJAAx9ifnVlwNZ7vxYEh8GAEHO8DDH5H5U0IPK8jHxSzFQAMnOKgJkFwPT6UBlAII5z3zQCjnA5OKBXeuAT9KABMA208DtxQHRhzgUC3KjJx9z2oAP6/L3NAHC8Hg/XNAcNtGe4oEy5yeaCdLk7yx2qQCAO1AmXZSSexHbPNAhJuLJkgjvzRonuAJy2cd8UCbyOi453Dj7GiYTZyVPPl74oYLJIyq68EH3Gf3oYTDEjLbiP1FEDHOUOdgOfXIBFAm77j5Mnng/WgLI5UE8Eg9iO9AnuJbuQx5wOBQFRxuIbOc54PrQK28ws76F722EyI4d4HJUOPb35yKBm8oeQsi4BPbPb71RyYIHmPGRg00GRsbsHIPY0Bg52AEEseBUCQJyOPXtQDtcdvvjtQCQ/GBwKAuXU4PrQBvZE5IGeO1AffjBJ57UBvEO045HagFWAAzktQKIzBeMg0C5kz5mOG/WgMrDJJ7jmgEnIyOccYoA3cEMRj05oC7/wDeBQTduzEoNxwcZGaAJOWfPNAlISVOT60aIQfkj+amgJ3bnnigKeFGPQUCf/x0Smw4V8exogX/AOY3+/SgKxKxeU459KAgJOckntQJkkcgkGgAAFFz/XQEmJaY7jnk96BM9yPQelAf/wCX7UBv/jagGP8AKB6ZoDf00HMfO/0oAH5TQA/5moECSMDPFAvGASMjPP8AigVX+b60BW7/AHoHEJJD55oDd4snv70CsSjCcDmgVAAbgYoGYJ3nk9qBUAYHAoP/2Q==
\ No newline at end of file
+Pandoc Test SuiteJohnMacFarlaneAnonymousJuly 17, 2006pandocPandoc Test Suite
John MacFarlane
Anonymous
July 17, 2006
This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.
——————————
Headers
Level 2 with an embedded link </url>
Level 1
Level 2 with emphasis
Level 3
with no blank line
Level 2
with no blank line
——————————
Paragraphs
Here’s a regular paragraph.
In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.
Here’s one with a bullet. * criminey.
There should be a hard line breakhere.
——————————
Block Quotes
E-mail style:
This is a block quote. It is pretty short.
Code in a block quote:
sub status {
print "working";
}
A list:
1. item one
2. item two
Nested block quotes:
nested
nested
This should not be a block quote: 2 > 1.
And a following paragraph.
——————————
Code Blocks
Code:
---- (should be four hyphens)
sub status {
print "working";
}
this code block is indented by one tab
And:
this code block is indented by two tabs
These should not be escaped: \$ \\ \> \[ \{
——————————
Lists
Unordered
Asterisks tight:
• asterisk 1
• asterisk 2
• asterisk 3
Asterisks loose:
• asterisk 1
• asterisk 2
• asterisk 3
Pluses tight:
• Plus 1
• Plus 2
• Plus 3
Pluses loose:
• Plus 1
• Plus 2
• Plus 3
Minuses tight:
• Minus 1
• Minus 2
• Minus 3
Minuses loose:
• Minus 1
• Minus 2
• Minus 3
Ordered
Tight:
1. First
2. Second
3. Third
and:
1. One
2. Two
3. Three
Loose using tabs:
1. First
2. Second
3. Third
and using spaces:
1. One
2. Two
3. Three
Multiple paragraphs:
1. Item 1, graf one.Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
2. Item 2.
3. Item 3.
Nested
• Tab
◦ Tab
* Tab
Here’s another:
1. First
2. Second:
• Fee
• Fie
• Foe
3. Third
Same thing but with paragraphs:
1. First
2. Second:
• Fee
• Fie
• Foe
3. Third
Tabs and spaces
• this is a list item indented with tabs
• this is a list item indented with spaces
◦ this is an example list item indented with tabs
◦ this is an example list item indented with spaces
Fancy list markers
(2) begins with 2
(3) and now 3with a continuation
(3) iv. sublist with roman numerals, starting with 4
(3) v. more items
(3) v. (A) a subsublist
(3) v. (B) a subsublist
Nesting:
A. Upper Alpha
A. I. Upper Roman.
A. I. (6) Decimal start with 6
A. I. (6) c) Lower alpha with paren
Autonumbering:
1. Autonumber.
2. More.
2. 1. Nested.
Should not be a list item:
M.A. 2007
B. Williams
——————————
Definition Lists
Tight using spaces:
apple
red fruit
orange
orange fruit
banana
yellow fruit
Tight using tabs:
apple
red fruit
orange
orange fruit
banana
yellow fruit
Loose:
apple
red fruit
orange
orange fruit
banana
yellow fruit
Multiple blocks with italics:
apple
red fruit contains seeds, crisp, pleasant to taste
orange
orange fruit
{ orange code block }
orange block quote
Multiple definitions, tight:
apple
red fruit computer
orange
orange fruit bank
Multiple definitions, loose:
apple
red fruit computer
orange
orange fruit bank
Blank line after term, indented marker, alternate markers:
apple
red fruit computer
orange
orange fruit
1. sublist
2. sublist
HTML Blocks
Simple block on one line:
fooAnd nested without indentation:
foobarInterpreted markdown in a table:
<table>
<tr>
<td>
This is emphasized</td>
<td>
And this is strong</td>
</tr>
</table>
<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
Here’s a simple block:
fooThis should be a code block, though:
<div>
foo
</div>
As should this:
<div>foo</div>
Now, nested:
fooThis should just be an HTML comment:
<!-- Comment -->
Multiline:
<!--
Blah
Blah
-->
<!--
This is another comment.
-->
Code block:
<!-- Comment -->
Just plain comment, with trailing spaces on the line:
<!-- foo -->
Code:
<hr />
Hr’s:
<hr>
<hr />
<hr />
<hr>
<hr />
<hr />
<hr class="foo" id="bar" />
<hr class="foo" id="bar" />
<hr class="foo" id="bar">
——————————
Inline Markup
This is emphasized, and so is this.
This is strong, and so is this.
An emphasized link[1].
This is strong and em.
So is this word.
This is strong and em.
So is this word.
This is code: >, $, \, \$, <html>.
This is strikeout.
Superscripts: abcd ahello ahello there.
Subscripts: H2O, H23O, Hmany of themO.
These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.
——————————
Smart quotes, ellipses, dashes
“Hello,” said the spider. “‘Shelob’ is my name.”
‘A’, ‘B’, and ‘C’ are letters.
‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’
‘He said, “I want to go.”’ Were you alive in the 70’s?
Here is some quoted ‘code’ and a “quoted link[2]”.
Some dashes: one—two — three—four — five.
Dashes between numbers: 5–7, 255–66, 1987–1999.
Ellipses…and…and….
——————————
LaTeX
•
• 2+2=4
• x \in y
• \alpha \wedge \omega
• 223
• p-Tree
• Here’s some display math: \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}
• Here’s one that has a line break in it: \alpha + \omega \times x^2.
These shouldn’t be math:
• To get the famous equation, write $e = mc^2$.
• $22,000 is a lot of money. So is $34,000. (It worked if “lot” is emphasized.)
• Shoes ($20) and socks ($5).
• Escaped $: $73 this should be emphasized 23$.
Here’s a LaTeX table:
\begin{tabular}{|l|l|}\hline
Animal & Number \\ \hline
Dog & 2 \\
Cat & 1 \\ \hline
\end{tabular}
——————————
Special Characters
Here is some unicode:
• I hat: Î
• o umlaut: ö
• section: §
• set membership: ∈
• copyright: ©
AT&T has an ampersand in their name.
AT&T is another way to write it.
This & that.
4 < 5.
6 > 5.
Backslash: \
Backtick: `
Asterisk: *
Underscore: _
Left brace: {
Right brace: }
Left bracket: [
Right bracket: ]
Left paren: (
Right paren: )
Greater-than: >
Hash: #
Period: .
Bang: !
Plus: +
Minus: -
——————————
Links
Explicit
Just a URL[3].
URL and title[4].
URL and title[5].
URL and title[6].
URL and title[7]
URL and title[8]
with_underscore[9]
Email link[10]
Empty[11].
Reference
Foo bar[12].
Foo bar[13].
Foo bar[14].
With embedded [brackets][15].
b[16] by itself should be a link.
Indented once[17].
Indented twice[18].
Indented thrice[19].
This should [not][] be a link.
[not]: /url
Foo bar[20].
Foo biz[21].
With ampersands
Here’s a link with an ampersand in the URL[22].
Here’s a link with an amersand in the link text: AT&T[23].
Here’s an inline link[24].
Here’s an inline link in pointy braces[25].
Autolinks
With an ampersand: http://example.com/?foo=1&bar=2[26]
• In a list?
• http://example.com/[27]
• It should.
An e-mail address: nobody@nowhere.net[28]
Blockquoted: http://example.com/[29]
Auto-links should not occur here: <http://example.com/>
or here: <http://example.com/>
——————————
Images
From “Voyage dans la Lune” by Georges Melies (1902):
Here is a movie icon.
——————————
Footnotes
Here is a footnote reference,[30] and another.[31] This should not be a footnote reference, because it contains a space.[^my note] Here is an inline note.[32]
Notes can go in quotes.[33]
1. And in list items.[34]
This paragraph should not be part of the note, as it is not indented.
2
http://example.com/?foo=1&bar=2
5
title preceded by two spaces: /url/
6
title preceded by a tab: /url/
7
title with "quotes" in it: /url/
8
title with single quotes: /url/
10
mailto:nobody@nowhere.net
20
Title with "quotes" inside: /url/
21
Title with "quote" inside: /url/
22
http://example.com/?foo=1&bar=2
26
http://example.com/?foo=1&bar=2
28
mailto:nobody@nowhere.net
30
Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.
31
Here’s the long note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the footnote (as with list items).
{ <code> }
If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.
32
This is easier to type. Inline notes may contain links[32] and ] verbatim characters, as well as [bracketed text].
/9j/4AAQSkZJRgABAQEASABIAAD//gBQVGhpcyBhcnQgaXMgaW4gdGhlIHB1YmxpYyBkb21haW4uIEtldmluIEh1Z2hlcywga2V2aW5oQGVpdC5jb20sIFNlcHRlbWJlciAxOTk1/9sAQwABAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/9sAQwEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/8AAEQgAFgAUAwEiAAIRAQMRAf/EABoAAQACAwEAAAAAAAAAAAAAAAAICQUGCgf/xAAjEAABBQEAAwABBQAAAAAAAAAGAwQFBwgCAAEJChEVOXa3/8QAFgEBAQEAAAAAAAAAAAAAAAAABggA/8QAJhEBAAECBQEJAAAAAAAAAAAAAQIAAwQFBhEhszE0NlFUcXR1tP/aAAwDAQACEQMRAD8AqQzziPNmpiqnIO1q4H+WkB84MdlzRSuM82/jVw/JCORtRmQz5d2VTy6WmS2eSYx3U/qkSRbgFsqRzH2Is4/mCluXc33vy8xTnJjTNqV/T8LKmkhr8Hq1da2aOvTfIh2CFeNt+GxFBP8AJFdFUbPWh+4FdXV7OtZOMR7mK9lBWNN+JBmMQ5cwmfH8DEFhTZUCRlE6CBq/ds/nBh9oYygeY1L9FnCUnBSN1t+w0l9bNomx1cllsOrL9OCTKtKOIqua6UVjP0dEvTyM7gp/3whbkAD0ScX3r6MLg+C2/XsMhCnJRn/5cVNHyJHiX6JKIFhhqnFeagm9BIgjfcJyNBTZiROBUk6Mp8CJRmT4NWU2MatV7n495DPk/wAbMJSRJOTBDItq0KR5s/nJN7LPW8AJWtYAoKQaDp+u4XShxgXhYcbHoxNTllCwETGQ8ag2jmDVsk8w/wCOp/C/hn+mWV/utpePH+D5wmF39NY6UakjUYR1Dn0YgRM5zQAAAMdfAA4AOAOArjkMNQ3vgm7UKtBR+m9QHFD5tpnDtpy+t2R20gK/OsmFtuDpaL5mVyiT5qdEVAvZci5ch5VoSGKbwlWTBr0RPoZT07av9lHfrXo6yLApWMugKpPM9SV1cDm65s/wkOHZBojoqiM+6GpMSj4FhtayNAUi5H3LfQBG2KWssFoSPuJdKyMLKtpuLi+e3jwFICUg7CSHsNVlYlKdizOTvKdq3KTsG8pQirsAG6vAB5FdhP490U4gfjxi+DedoqO4YftmKdKNulO26jiOv+2Ga/bftVNFXpHtVHrpLpRFJTpP3z77T469++fTx48e4LueE+NY6UKk7UniLP8A7rNf3X6//9k=/9j/4AAQSkZJRgABAQEAeAB4AAD/2wBDAAYEBQYFBAYGBQYHBwYIChAKCgkJChQODwwQFxQYGBcUFhYaHSUfGhsjHBYWICwgIyYnKSopGR8tMC0oMCUoKSj/2wBDAQcHBwoIChMKChMoGhYaKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCj/wAARCAD6APoDAREAAhEBAxEB/8QAHAAAAAcBAQAAAAAAAAAAAAAAAQIDBAUGBwAI/8QAPhAAAgEDAwIEBAQFAgUFAAMAAQIDAAQRBRIhBjETIkFRB2FxgRQykaEjQlKxwRXwFjNictEIJEPh8SZTgv/EABcBAQEBAQAAAAAAAAAAAAAAAAABAgT/xAAbEQEBAQEAAwEAAAAAAAAAAAAAARECEiExQf/aAAwDAQACEQMRAD8A2t0YoQpwT2qVzMV+N3UHgrDY2eoM0y58VEbgfp9K1yMRmnuJ5h40jyYHGSeKrWE8u2QAApOMdqGCsmT8h70TAJwMAZx249aKBy4c9vTNUC0zDCgmmmG7Ockjkj1PrUTAjcy5XP0ouCgHae4IomOJHhgIc55PHY0Uk5IXLMcUBQ27n96JYO2MYLebHtRBA7BcMx29sdxQJqwZRtIP+BQKpjHHc+xzigNGoAO/k+nPAoAYlee5oBiGeWySO9AJCgY5PHagFCADzj2GaA2N2TkjA/U0HMwbPPeiyBLDfkkj04FCl1cBMgn6URwYFGySR6D2oAeQDAxnHGKAhU4IbGc+tFwnwDj9aK7f8v2oNu+IHxNvJdXmt9EmKWSqArA/mPvxUxMZNe3Ml1dvNcMzSSEsxPOferJhht/OWyAPc0UfdgDcuM8n50AMCykZFARsngcY/egTcbjnJz9O9AB2kZGSQOcUCX8x83bntQCMruJ4B7D1oCyOGzxtJ9M80CAdg5UjFE0aFJrghLeNpHY4IRdx/QUNWCw6D6q1EZttEvirHAZ4ig/U4qw1b9H+CHVN3Mq6hJaWMJ5ZjJ4hA/7R3P3q3ET+pf8Ap/lWNm03XkkkA8qTW+3PHupP9qxopV78G+s7VSV0+OcAn/kzqSfscVvIKzqPTWu6XKE1LSL+Bhz5oDg/cd6lEZzGwLrtPqrA8frUCJfcw9gfegUjZsEAffNADyHt78UAjCjzDJxRcO5Pw3gwCGOVJQp8ZncMGOeNoxwMY96GCbQffFFcUXKjDDt2NEo+N3yyM5z3okKuqJgIzONoJyuMGi4QfGcqSfXBoYHJx659qKIRnnsfUGgJn/poJYoTIGLY+eDzQFlQK2G/KCTmgbspfO0qce/agPGcR7nHf9vnQFfBPlOc88Gg7uucc/M0Bd208YJJweKAYrea4kKQICRGW5IUYUZJ570DYqcknt3FE0VuVyDzj1oamOlulda6puvC0a0eZVIWSbtGn1Y1NNbX0x8ENH0qL8X1NdtqDoNxiQbIh8u+WpqL70Tc6fcxypouiRadbW8hhLFFXcB7Edz+tNFvEZxkmmgShbA9PlUA+Hgg/wBqDgmBkd6ArJuJBGR7VdEdqWgaVqMfh6hp9pcLj/5Ig2KaKJrvwW6S1EFoLaWwmPIe2fAz81ORTRm3UfwI1mzBbRL+K/ReyS/w3x/b+1Wexmev9O6xoE2zWdOubUDszr5T9G7H9auCJj2n3PPrUXTlGBB2kYx96GlQMjJJHuRRXBgDgk8DtRKH8w4OfYA0SUlIMsFXJ4oujHH8ufnRRGOSNoJNAeFC77F2jPucfvQFEqgY3nj/AKaCUY58wwq54AoCzOmVMke9QeRnGR7ZoEIF7pnaTk49KDpSSwQntQJsGKjgggZ9uDQc4OOe1Am2UCkHOR7dqA8t/cSW8MEkrGGEsUTPCk4zj9KJT3pzQtS6m1aPT9Jh8SVxlmJwqL/UfYURuuhfArR7f8NLrF1cXciKDJCrbI2b7c4+9NGtaRptrpdqltYW0VtAn5Y41wBUodvGjqUdQyn0YZqAIreOBFSFFRF7BQAKA1xcRwKplcJuOBn1NAR7y2ikWMzoZnGVQHJNAuQcD3oBKkD2FBy8jnvQFxnjjmg4rxwKBMqCBtPNA3vbCC+tngvYo54HGGSRQQR9DV0Y91n8DNOvFkuOmZmsrk5PgSNuiY98D1X+1XRhWu6DqWgX72er2j2069t/ZvmD2IoGG7jbnj1FFlB224PB+VClN4DYJHyAojmPGCck8cetCAxgjPp6UaAGKtx6+9ATAXO7nFBw8HHLN+goJhBuj2FeAcnmgNazW8U0vjweODGyqpYrsYjytx3x3oGa5LEEjH9XvQGlgmjjMmQq4HBPfPYgevagG5nhe3tkFuInQHxJQTmQntn0wKBKTlAeDx60DSY+U9zn+mgsnQvROr9Y3W2xi8KxV8SXUnCrjvj1Y/IUR6c6A6H03o6wMVgrSXMoBmuX/NIf8Djt/eiLfjJwO9ZBiOfmKDhktzQAzYBLZ8oyaDF+rOptVv8AUjNZL4tjA/lT+kr3wvqTQX/pi3Y+DqFxKXurmFWAaPaVzg4I/b0oHlxqV7penRTXFu93dPLsESYB2k8n7CgnradLq1WaIOFI/K42sPkRQCg3Kcd6Dgp3d6AdrGg5VxnjmgKWB8uQGxnFAUgKuSefSghuqNC0jXbAWGtxQyJKdsYc4YMf6T6GtDzR8S/hnqfSUz3NvuvNILYSZR5o+ezj/Pb6UGfLzyD/AJoFFySQVBHpQDJ5kGByPahAbWxn5+po0OF3D+XPtQJsNwOe+aAuygmMkebgHnHFALHYpJwSeGz2oGpOJWAI49BQEZlYAHkg4oARVOMvtBIJJ7AUAX6xxSOsUgmjViFcKRuHviiVfvhT8NZuqpk1LVFeHRkPlHZpznsP+n50qPS+mWVppdnFa2cEcFtGu1I41ChR8qyHVxK8cLPDD4kgGVQHBNAa0maaBJGTYzDJXOcUCy5JOaA2OMfoaArkheM7vlQNYNOtoWLJCgLHJwo5NApPKLaNpGRQB6j2oGmnRvcyNd3O/DkeErLhkWgklIdCyZOCRzxzQEeRxhdpUnncBkD5UCxXjJ7+tAlctMsIMLohz5mcZAH09aBQYdQwyAeaAuA7MAQxHH0oG1481nbGVInuWU5Kr+bHrgepoKB1u+o6jqlvBH05NevEBPBK0pQR4I4BHZj+1Bb9IS7lsFtNWtYwDGFYB/EXHqpJ7/WtQYx8VfhGbdZtV6Uh8gy81mpyR6koPb5UGKY4YkeYd88fbFAI5AC98c5oQBb+U9+9GnN5RgDgjOPWgAN3yMfWgAqc91/UUD2RSSRg9+49KCR6e0WfX9WS0icRwgb55WOFijH5nP0FBYNRi6dSR7HRNPmu0hOW1GaXaZMdwBwAP3oynE0XRYrFtV02wS4ECj8dp1wcsE7eJEf39qlFZ616ZttPu7Kbp9Zbi0vYzNCcgjHqoHuKsEp8LPh7P1PqjXerxywaXaviRSu1pWH8g+XuflQemIIY7S3SK3hVIo12pGoAAA7AClEL1N1RH0/oTalcwx+IACLaSQKx59Ppmshv0D1jH1ZbTubU27xkkAnKsuSMg/UUFluLlLaJXETyecKAg554zigXiubeRnSKeJ5FOGVXBIPsaBLULoWkIfw3kYsAqIOSTQJMbpm3oqlmwACeF9yfn+1A+Bx34oE5IY5P+YFbnPIzQKAckHuRQCAQOO1AL8r9KDhkZOT9M8UCcrxgAyYJzwD70CT3Itxm8kgi3fly+P7/AOKA9pskhEkZysnOfeg6RH8w3tgjAHtQRZ1uystSg0m5eRJ2UbHceV8fP3oJkBSAVII9xQFdSRwKDDvjN8L/AMSJte6chxcgFrm1QcSf9aj39x61YMH8Q+CkfhqpQncxBDH5H6VRwXJ/Ke1Am2QchuMYOaNFSAVznB9qAm8f10D2RmX8jDHP3oLbebtA6ej0m2LrfX6LcX7IMskf8kf6HcffIoG8yTadZxSTxCK3kRZUwSFfkruIJ78GhiS6Y1OS3160uZJFWO5bwZtxzuQ8bcfPNMZXvo2wsLnQ9R0q/maJNNv5Yo3bjCuMAHPzqA2jdUan0lF0/ZXcElxp9zE+5WVd/DE71IPPB7H2po1bSNXsdYthLp1ykyEcj+ZT817ioITrnoux6vs1gv5JYnjz4ckZ/Ln5etA+6N0BemdBttMina4WEFfFdQpIJJ7D60E5I4Vo9qnnsQO1A3k0yzeTxhCizZJ3qNpz9RQO449igMSxHGW5NAIwBtUAUAMORkfegMhG3jtQD8+fvQGXJz7UAHuRQA5YDI5FB0qCQA5yaCs2/SFit/Jd3AmvJ2bO64ctt5zwD2oLMilVAUDgcAelAJLbhgZz3oGN9HPIYmhtrWRw2czjt7Y+dA+h3mJS67W9gc0AvuLYANADpkZABHY85oPOnxy+Hx06Z+odGjC2jt/7qBRwjH+cY9D6/OrKMebcceHwfaqCYIyDgZ96GhHOFJI4/WjQpXnsaCz9J6fDqGvRC8OLO3Vri5PB/hqMkfc4H3oDT3UupapcXrKS9zISgDdhnAGPbsKC5aLLBHq9p01c6bbagPE23kpJYhmz5IySAAMj6nNGdRnT2lu3V9vaQQrJDHfCMFj5kAfufsMUFogu5H0jrLUYXK+Lq0aRse/lf/8AOKlFfudagvbnQpNQRmtILydCwPdCQcgMOMZFQanPoeiawBd9M6s9jeKPK1vKQp+RFA4septa6fuFtuqbRrmzx5b+BAdo927A+vsflQXfTr2z1O3W5025juIW/mjOR9KAZI914khaRNo4XdwT9KAl3b2+oWpjMoZWbOVfnI9sUCrXUNssUU8w3sQoJH5jQLvwQQC3NAKvuUPtK54waDg23v6UA7weBnNAIOBigMr+hoOjdZQdhBx3waAVG0Z7UBWfAOQSflQChyNxBAxQRutarb6bHALi9trSW4kEcJnGd7ewFA/j8QEK/IA/MBjmgWDDBB7igj9dupLTTbiaHZ4oQ7A7bQW9ATVgwXSNV6onl8azW6t45pWdxHIxWA/zNtz7A8Glg2S1u7fX+nt0J/H2c4MMhmQoW9GBUjj60g8sfEHpebpDqi4sHLG2Y77eQ486E8fcdvtVFekGW4UfegKVAAKgnFGhuDzxQXbpDTZF6a13UnUqrCOzQ5wGZmXIJ+lE0ppkEK6nJcRWcTW9hA08iKcjcowpye/mxQ0+6VRbC/jvLm48L8LG9y8pIOXxkDnuSTipqHXQMng3es9S3fhn8DbvcZI5Mr/lH700dc3Dad8NtPs4nU6jeXD6nMCwBRF5XOfU8YHrTNJFF1X8RawW1jc4GxTKNrZB385yPkBTFw1stSu7Ni9tPLGSQfK5Aphi8J8UNUm6fn0u72yvJ5fGbuF/39aYYtGgadp9/axXnRetzaXqnhqZI3bEcj4547Ak/X6UxFisPiXe6NMdO65057eQAr+LhUlHHbOPX07UwWXpQ6BqMo1LpgW0sioVI8Qgxk+684qC028M5890Y3kHKbUwF+lA4LDOzu2M4FAOG3DaoI9cntQdJxzQEyR259f/AKoGl5fSQRFo7ZpB/MhYIR9zxQdayyXKb7gqox5Yo2yB9WHc0DPUIWnhWKxkuYFRs5gcKWbPY59KBkx6isVeSGW31JNwHhyOUkA+o8v9qCfjkMo/LJFKqBmRvSgc2swnRyFcYODuXGfpQMtRsLK8vYJL+wjuGiUtHK6hghz6Z7H6UEmCsig84I9RigiruC9t0DaaVmIIHhTOQMeuGwT9qCJ1ywv9T0U29xFFiaVBJGHz5M5ODgYPY/arKJPTtLW1t44i7SKq48w8x+ZPrTRJoipGFQAAdgKgzX47dMJrXSrXkUe6807MykDkp/MP8/aro80FQyZ+tUJ7hvH0x270XQ7KGtXvIk0T4c9P2bIhkvpnvJVfjIxhf7qftRDXpu0/1DpzXltUlkvmWMBI+2zdnn64oYa6yX0XTm0i4jQ3t6wmuV53xov5UPpyeeKyLbpFtZ6Xpmn6TqNq7/ic6pqQRR/DVf8Alq2fTOP0FXBnXU+ox32o3lzeW+JrxlMXHKR9wfbJ/tVWK5f3AnaAjafCTwwcY4BOM/qKKSjA4Dg8j37UHZKkE5P0olSFlcLDdJPbTNBOigjxOVZu3+80Rbbnrq9l0t9I6isRd2rgKpPlZMdyre9An07oupoh1zo2+lea2fMlr+WZFx7ZwwqWDVug/ihDq7R6b1EPwmpMNokPlVj8xng1BqEUe1EAJOMDOc5oDSxq6YYeuaAJF4oCBUQ7mJ45zQHYB14wR86AVjBXyjge1AEcRTHlA9hQE8kbgEohJ5yQM0ETHNqMOr3IZQ9tIMQyEjKt7D3FBLqywRPJKTuxlj3zQI3Ut14e+yhWRj28Q7RjH60EfpF3rU/jLqFrHbS4/hqpJXH19aCRa8jgiVr1xGwXzYyf99qA9tc29/aRXFnKs1vINyOO2KByoxwe9AYocHGKBvdwLcWzxSLuR1KuD6gjBoPHXWujt071Nf6YSSkUnkJ4yp5H7f2rQgWAA3Y+1An4j/1t+tBrHxKuYS+gx24LRx6ZFtI/lz60FY0+/v8ASphNpd68EpXY5AGNvzFF1YOirZbzVrvX9dkNxZWH8eeaY5Lyj8qj7kcVlETqOqXd/HrPUNzcNE16Tbwxf1JkEgD2AA/etBte9R2Oq2cv+p6XHJfBFjgmjkMaRgAAEqO5o1FWfbgjsR8+9AlI5CgEggeoNAq0iug8uD7g80KKmCcZ7fPmjJzJfT/hWtjJvhOPK/OOe49u9A96X1W90/VrRtNkkSfxQF8I5yScdvX6UGidSLpfVFzcvbRiy6kgZBGysFW7B9T7HHNSjU+o9S1iz0e2uNLmX8RYxJ+KgYeVwVGTn5d6gjug/iU3UOt/6TewQpP59skL5B29x/8AYoNHPB78Ggb2l3bXO78PKsoyVyvIBHBFAoSkbfyhn4GfWgTnmWFN7ybAvc4Jz9hQRdx1dp0S3Dw+JJHbDdPIUZUjX3yRz9Bmrgzbqb4x9Oxho4bB751O5HPkXPsc80wQHT/xrJ1IHUbGKO0kdRiBiAgz+YjnsPpTKN/tLy3vLOK5t5klt5F3LKhyCPemAYLuK5XMDEj1OCP71ArGWLMPT0oIbU7h11u2t49OllWWNm/FIRsjI4AI/egfQ2ktpbww2XgxoDl9wJ49cUCHUGv2GixM13Mkcm0squwUH5/SrgxDW/jFcXOteHb3otrKEEiRISRM3zGc49v1qDT+gfiBpvV7y2unxTxywRhz4ozuHbOR2+9Bmf8A6kNIEWpaZqiooEqtBIR6kHI/atfRjDEt3AKjgVQjug9j+lQWh72e/htTOzyeCnhHPomeMYoJvQum7vVD47K9jpsQBkvZ5NoAHcgUAa7rKamE0Lp9Xh0G1OZZTwZSO8jn9cCsivdS38F9cJDZIY7G2URxKe5x/MT7nNaEKrENwAFPPlosFwS2cd/cc0UlIm3JOeKDo2LH+UA0SjgDk98URzPiJ2449e/NAbS7v8PdpKkpikQ5WQLkqccGgmYNQmXWLeQLG9wVRQVPlcj+Yn3xQa98OviAjz3WjdXSpFdliEuJCNjDtsJ7enepRdel+kdL0rqOTVdIsoYklV1dixO3nunpg9jUCnU3WMeka5b2EUcl3JInmigQs6ZPlJAHY8+vpQP9O1m3nthNo0cTwM2JDwoVj6H5gd6CbhtUiVn8TcXO4ktkZ+We1BAf8Z6fZ2uqXWpyxQrbStGseQzMB2IA961B59+IHXmodXal+HsPFh04HbHCo25+bY/zQWv4f/CCxvII73qC8iuXYb1tYZeF9txHf6U3BatX+DvSl86x6cr2dwjbnEUmcj6Enj6U8hLdJdEX/SmowJp2tTT6Oc+La3HO0442+3NBf1LmRUjjQAfmc+nyHvWQockYyQcY3CgaabaPZxGNnaUFi3mPb6f+KA2q3RstNurnBxDE0mPfCk1YPMemaP1L8RtYN9fJPc2aMUaVmCKg54H0z6VRYendf6Z6T1W56a6j6fgfwJyguhGJmPzbIzjHtSjTn0zSunbi01fSkt9Os5GAmWNCDOGxtXb6HnNZEZ8etOF90DPKFy1rKk3zAzg/3rXI8u7zvOTg4zVoTLDJ81QWDTb2SwuvFgcrkbXwM5H0PFGqsjpd6+kcT61Nc2ieb8OikFc/9PA+WfSjKA1nWBzpFlZ/hLWM4KH8zsPVj6mghN4IyQRk5NGo5BkFmyAfSgVjChdpGO/FAXYpOHLBe/FAQqoBJbA9sUBGxgtgEj/eaCf6DGjt1TZf8RNGumKS7mQZQkDIB+WaMrf8Ub/ovV7V20JIYL62K4khhCLOCcEcAdu9BmCuEQvxvyFUg42+v+/rQaj0zax/EXRY9Nns0t9TtM+BqCKAjEclXA98jn+1Si7Cz6u6O0tLjTrxLu2tQJJrDwcKE/m2M2SfeoLrpupDV9Mh1OytUS2vIN8m4BZQf6T7+vPpj50GfdK9L6rJqk1y1y0elRDKRqdjHHoyDhjx39e9BZr7fagW0j3kul3iETRqHkeF8ZBUjkZIxjtk5rQ86dW6r+O1OcW0UtvaRsY4oWfLKBxz7k/5NA46P6X1rqS6WPS7V9v88rAqi/f3oN46X6C1DSotkus+BIwKl8hn2+3PapROXPT2t20bPY6kJ5UGYmbIfIHGW5z68VBI6DrzzWSrrAjtrwFUbDja5OBlfuaCbluJLeNwIpLiVF3bVXAP0Pv8qBxLO8cYcW7vnuqkAigNFKs8CyxlwG/lcYI+1A31ayF/pt1auSFmiaM/LIxVgwfoO413o3qqfSLyUSwodogAyZVGcbPTPr71aNDvendJ6wtbu7Fi1lezK0bS4VZMjtnFZE0bC5u9Jh0qRAr2yw4uWx59vBI44PegN1tpbap0lqOk2sipLPB4aFsnHbBNOR5A1exFhqFxbeKkngyMhdOxIPcVuhiZFz/zBUEwcKvYnP6fWi0+6chjn6h062uATFLcRrIMnzAsO9EehNR+GvTV3GUh0+O2YsGaWHIf9amjIfib0no3S0VtFY3M000zMzLJtLKvvkenyx96oz0rwNjA8cj2osFLbVAbOc9jRQiXOAwxnj3oBlAxwDj37UDY+vHOQeTQBIdqjcPMfnQwJclWyBgCjJBFeefw4VaVycBUGST2wAKD0L8H9C1rSIILjWLSCytY1lZASVnlL4PI/wD8+vvUo1uwbxI5GkjdVc7isvOBjtj2qBWKFZiQ8CJCB5FHYj5jHFArDbQ20ey3RY1HOAOPsKCH1u61CPSLt9MtlXUHUrbCbJBbPdtvYetXR5T1y2udD6lni1ErJdJLvlK4wWOCePvVgsV/8Sr67UW1vA0NiowIonMe4+7FeT9ARQRmodWa9EYpPBhs1Tygw26rk9xknkn70EjonxZ17TXjAeKTkZ3L+YZ7N8vpSjX+lOpNM6umgkMG3EgBV1DYbG4kewz2NZGkC43CP8MPFBONysMAD50DaHVH8S6N1a+BaxMUjd280pA5wPb296DrXWLK9WNoJdtwybxDKPDcAnHIoJBifTBzzmgaz2UFzPFNNbwvLCcxuyglT7igdRRKg8qAZ5JAAzQEnuYoHiSWQIZW2ID/ADH2H6UERr12BY6hueIQJaO7SK/nHfnHtx3pyPGWoN4jynuCfU963RF+DL/UtQWTkjaWY/8ATnHFGql+j1VerdJY8r+KiJz/ANwoy9C/EjqSbpbRY723RJC8ojIcZ4IJ/wAVkecer9en1+9FzeLCCq4URjgDP7mtLhteadBY2kMczyHUpcO0YxtiUjgH/q9celAiLy1kjCX1ruyMLNGdrj0+h+lE0+t+kNQltJ7yKS3jgiTxUFw/hySp7qp70NV6YEBgWUNjBoaKeAODnHrRoVgDnBP0ozpxZ2f4y5trVeGuJFiBPpk4zQep9C0LTembS30fQbWP8ZsDyTugZgf6ix9fYZpbgmbXSmXULaa6kMzpltzcjJ//AGpaLCY1CDsF74PrUCgHY0HbSx7Z96BGUfxB2xjtQZ11t0Tb6jNfyw2wM18gV5AcBdpzyPnV0Yp1F0o/TEczXjXaTOQYpIk3QlT3B9Rj0zVl0VKbVppImheUSwbsgFfXHc0De0tri/ujFYQSSyfmKopPHqaDV/g9p+padr/gkSRTzKu0kZRlPLYPbOPf2pg9GWzRCMJAFxH5do4wayKX1z/G0CdzqLWRkiaTxQBLudclQvovbv3oMU/4Z67uwnUAt3u1Zw42yhmx3/Ln8v0oN86L1d00i3i1UiGQIocNnEbnkqT2xgiguEbI4DIysp7EHNAZnxQQ/Usksej3EsCl5EUthR5sY52/Mjigr6Qrp3R15LqEcIlmgdpFGAsY2navPJApyPJtwd8rnGBuJz6Gt0MzGSTyf0qCwSKA5ZsAjnn2otTXQYj/AOMNIDqCrXUZwf8AuGDRG6fF6Gyfo6+ub0CR4EPgIScLIeAcfc1keatN0661a+S3sYTPKzAbV9B7/StLrQ/iXp9pYLp8elWsUM11AzXMqt53I7g7j244oiB6W6Tn6j2TeAy2FspTeB+Z+/8AmgtnWlvpdl1Dp1pq07Ja20GFQpuDHHAwPf39KDHriVTKSPOCeBnHHtQGsrG5v5pfwcTOIlMjgEeVfck0XRIreS7uUigRpJXOEVe5PtRE/wBJ9HaxqvUcdhNFJp0lviaSWVcMgzxgdySeBipo9T6O8NppUJ1K4iW5KgSvIyqxb5jPH0paJm1NvKivE6Mp7MpyP1FQLRTwy58F0cjuAckfagOTtO3+Y8igMWCIWbOPlzQNhNBOWEbq5Q+YKc4+tAD7JEZgQfXj0oI/VtIttXsZLW5hRopByCP/ADVlGRa78Erae63aXK1tG3LAncM/Kmh10l8IZdBv4rxtTE0yggJsyoz6/P0po0zSNKEMdo9xGnjxuzkqMAEgjj7GmialjWQMgyCRyQcGoITqHT7q/a30+G2jFmwLSzl8GPBGFA9c5NBPRwJDbpHCipEi4CjtigqfWltqCaG8WhNbxyzOBIs8W8FcY4+dWQQ/wtuZdIGqadrknhy2u2QyOSEZOeRngY+XvTBZZevOmhC8janbqiZ53Zzj2FMFcs+sh1ZqsFrp8UkGkrlpbh+DNzhVX5Z5NQTfXyWUXSV2t+wW3EZ5I4HHt61eYPI0mA5C9snFaoLsPv8AvUEk5JcA8cZG480WnOlXX4PVLO4yQ0cyP244Yf8AiiPUfUump1B0/c2O8xfi4v8AmL3UcGpgw/SujNX0Trj8PpckimOMvHO/kEg9Rjs3PpV0aFq/Qqa1ZJ/qcrverEqNOwGM+uMfemiVtrKbQdMNjp9rvtkhPht6mU5yT8u1BkvXg1qXUtOvddgRY1R3j2YHiMvZSD27CgzSCyuNQ1KK0giL3Mz4VAOc/wDignoNNOnaHeiW8hgkku/Al2+Ziqgn09M0ETp0qpqSmGKOdFcEeLwMfPHag3JLuCRtPmQWsDhNphtVAcn1w3BPFSwDdWGpX1/OYdOtbbSrlQ80szHdn0GR24/c1AbWemdatLbTJdGvJIJypDQwMV3exwOPatSz9Ei/R+txy2mr3evyHV4miWIDhGwwyGA7nGRS2YNZAUBWYDdjGayEvxMYB3nYu4KCfU+woG93c2enWs1xcPFDCp8zEgDPzq4GGgz22saS1zZSZhkdsFePXt86YHWmySeLNDMYikZ4YNlvvUD+VARxQJqgwRQHUAAe2O1AWOFRM8mDlgB37fagb6reXFt4ItLZJnZsuWfaI0Hdjwcn2FAz0nWX1i4u4xY3VpFbv4eZ1x4vGdy/KgkriN2aMRlQoOW3DOR/5qwYr1P1tp2pdS3WnanKkGh24kRl2eaYgcb/AFxnnAqiv9Jno0dRLJPbtdQtkNPIALaMnODsPPpSjbdK0DTbWQXui+Gsco3BU5hPP5gPT7VkU74t6PZHpq/1N5ZZbwrtRnmOwDPOFJwPsK1xR5ybudw788VaC5X2WoJRULSBpAe5PA/aiinAZnHck4A70THq/Qr23/4Y0u4lmCpLBGA7epxjH60Du+WGOBvFlFuWOFcYyCfbPrUojri6k06xX8PFNfBUJ3ltzM3scVBjfVvVXVNit5dapNDZGQGK3shjeAe7YHIwAOT3zVggNTiu+orrR4p7m+upJFR7h3TPhggDaoBwRjnPH5hV0af0xotnoD3l5dWdrY2YjGLhwPEHoef996CC6m0HpuPpk3Wny2s9sJPHJ3AeI2D39T37UGU9QTDULuGPSLPwIyoVIYk2lj6/X70G2/DPp0hVudRuBLcwxhRGkeEjB9M+p96DSLprVHiieaAE+YxHkke4H1qUOIBawL4uAuc8nvj71AwjRtQ1eO78QNp9odyLju/qT8uf70Gb6r8SpLzryy0vp+4NxYSSCEswI2u2Rn3OOD9qC4dVamen9NlaC7tUaIFvCmnHiy4HJXJxnOeDVwed+rOvLnqSyWO4jZSru/kc7ck+30GKosXw2+KmqaDJDY3jR3OmqNoRhtZAP6SP7Ggtmt63qbTJ1XLazJpslwBFblypEOAA7L2OWANS+xrnR2vW3UmjJeWp8wJSRf6WHeoJdSPMCRmgMq8DmgBpNsgUIxBGSccD70DczmS8MDWoe28MN4+f588rj980CktuJZYpFdlKZ4B4OfegQ1hpIrVjbsRMBhBj8x9qsHnX/hm36y1O/u9V1ddPmS6aD8OkQdyxOSe4OMmqLUvwQsYY4Xjv7m4YEEhwFyMY7fXB5pRbvhp0jqfSMV7b6jqZvLGQAwxAEBDk54PuD6VkVb49a5DBpiaNaeF/FIaQDumOwpzMGDEZQZ5+VboR8In1I+9QWDY6gFn7jjHpQhtJEFbAGBnijT0P8H7qPVOh47a42yNaymPBOcDupoykep+m73V7g/8Av2itQowvJIx6j5/OpRjfUWrax051RPY6LqFy8YACkebO4Z7HjNWCY0ToW2utJbqPreW5na4O4R78cehY9+fQVKLX05p1ro97awC4kX8VFmJLeEKdoyfOxJPbHbHYVAz0rqKPWNauri9t1ktJgILYgEiNFJ/Op9STmrBBdeaFCo0y3jt444DI3jLE204Y5DD+9UPPhv0NaRtPq99mSLOy22nOfdh75oNC0vT7m1uJGvGiii3AW8UDbQAeDu9zUohLlhouqap1VciF4I1FtbxSthtobBIPuTn7VBJ2vUth1TYk2ULi9iALwyKQYz6Z9CM0Ft060/DWEcDHe2Mucdye9BFW3SekWt3LPb2cUTsd2UGCG9x7VYMzufhzdX/WmoXj+BPpx3I7XZMmXYckc8EVRKaP8I+nXikLQuxOQSTnBzj6UEjonw90XSrq3S3s7dplJcl1EhGDx396lFx1TQ4NVjaC7UNCU2lAO/8AvNWDCLp9X+E/WgWImXSp2LRq7eSRT3B9iP8AFSjd9P1+21TRodVsMS2rLmTbyUGOePXFQSltcLcW0c1vh4mXcjDswoDLdRm4FvISsgXeTghDzjAPbPyzmgVFxCzuiOC0WN3sM+5oDqySJmNg3rx7UFb60tNUubGJdFdEvhIdryflUFSM49TVgyTQenJemOorf/U4H1Fpp1edAh/hOQTuQ9375JA4q0bnbPBcxxT20wkjKkqYzlT9ayGWu38um2MbLEJ7iRtoUds+/wAgBzQeW/iHqi6j1PdzeL44HkL9txHtWhVUOVyvHNB2F9zQT8hUAhAdp5FCG0mSAzE4HGDRppvwL1bwOpJbEsFiuYyVX3deR98Zoy2ZtRgmjkSRZocEp51K7se3vUow/rfpFE124mVpfD4mk2MWdCc4A+VWCH1281/UmFnpklzPYRFBEG8uGC4yQfcn9alGgaJo95rRsbi53WaxwrHOm7BjYcHnvz/moJaw07pXSI5IW1K0CQnDhpAWB9R796CudY62msTRW+gadI8KnDXMkLLv9MA8HGOKC3dAXF1dRfh75f41moi4G0AdwcfTj7UFhv7RjqMBV5AJFZHkR8FRjIx6CgpXVNjJ1JqNn07p26CztSJLlpIydyj2J+fGaC+afplrazqLa3SKNIggx3IHYUEsBk4wQc4oK11L1z070/M9rql6wuVA3QopLcjNBDwfFboqeSO2W7kQNxuaEhQfnQLt8TuireVoV1UeXnckTFT9DigHRuv+mbu9ZV1W3Nyc4IRlVl9O47/KgtU+s6baw+JcX1umRkAuM/p3oK/1t0rYdX6cqXKESqN8Ug/Mp9P1qwZ702mo9GdUTWJsmOn3EY8CAORGXJAwScjJ5q0bJDNLb6YklxbKsgA3wwndg9sDtWQN3aw3ZKTwLLEQOGORn6ehoG1vYAw3FikRt7JSuH3Hc/GSc5P0oHn4aO2uGuYyiose044wBQIm6F1dwfh5ARs8R8L2BHGfnQHv9PS4PjxrGLtFKxysm4qD3oCxboIIo7e1jhQHzAYUJ8wP8VYM56j1ktaal1BMrS2sAaK1OQDD6eUepY9yfQVR5zv7hrmaSaRtzyHJY0DcE4BPIPb5UBwOO4oJYzFvzEYHAH9XvQhNZN7AEgDOSDRo/wBA1SXRdVtNQgb/AJUgfBHcZ/8AGaGPVlhPbarZ2t5CEeORBKje2RUrI1zYxTBhMinIwcjvUEcugWkO4AMisMEA8N69u3yoERrOhWNxNYy6hapcxAeJHM+D8u9ASLStLlm/EWdpZyxy+Z3RQ3I5B44oJKTT4blFWSNBEOeBg5+goFYbOK1TKhIxnIbGMH50Cpcyo6AMrIcM2OD68Ggb6Lbbllu5Cd88hYBu6rztWglSNkfm4P70Gaat8Rba96w0vp3R2mhufxyi4kO3YyDOV9+f8VYMw+P0cP8Ax4JVuEKzW8bEr5tuMj0+lUZ7Y2X4288GK+towRlZXYqv9uKCQi6YmbT2u11GzaJWKnYxbBB49KCFnhubdiwL+U8OhP60ElpXUFxY6nDdXQF0qYbZKxwT9vWg3npb42aHcmC11C3uLSQjEkpIdQfr3xUondP6x6e6tv7e101hczRzrNtaFiFC/wAxPYHtUF+lj8bYCTgMG59cUC4OBQQOo2eoXepFTeL/AKYQN1sEwWx6Fu+DQLX2kw3Ok3Vjas9qJ48Exd1PHb9KCE6R0G86Ut7mK71KK4gklM7TyKRIBjtjtjj96AOreudJsrMJbXksk8jBCbVdzRjONxBHP/3QQ9x1jcWGkERWWqXdpMPCt7x4wfFOOWPbA+fAqwZr8TJ9Qbp2ymvEjsrSTEVvawyHz45Lv6E4wPqaoyl8g91OKDlYEc8mgKW5PH7UE80f8PPHl7gDFAZkUjawUIQG8w5ouknAUbl9Dg59KK1X4Z9XXFvo8mlRXax3KHfBG8Rk3qe6jHOc54+dMZO7jr/qK8vWtba4tYu38TwvDOMc8N60wPLbrW10PS7pnvrnUtbAKobgBUUk9jg8f/lMC2rydMdRSaRqWoLEbx4UefwxkL2BVvvn9Klgv3Tp0lPxFno6wJ4IVmEOMEHsf2xUD2e4ks7n+NGDaCMu8q8lCMcEfPNA6tW/EwrMybEYZUHnI9Cf/FAzu7G4LXTWs38SRNqhs4Bz3z9KCO6x07UNT6altNMvEs7xkC7nPlI9R2/egwbrDT+r+kupLCeK9nu3KBYGRy+QvdWFWCU6avtA6h1iKDqLRhpmpvkxz2p8JGb3z7k557VRX77TdHteuPBut401CAouyXGcdvmASaC069030brYaay/CwPFwWspRErfUN7UGZX2hWSiY6ZrMc0CvhUlBUk/UcGgiLq2mtG8F54yDwfDfIoGkrRsSZXwOB2zmgsvw06XHVfUcFvI22xQ753Ze4H8v3OBUo9a6XodjpltHbabDHZIhVsQqBuA9DxznFQTQUe5oDYGMnn7UEbpV3JqDyz+BJFbBtsXiDBf/qx6CgDXL42cSRwGM3UzBQrHGFzy32oG2i2kKTSI80lzMow0rqQoyew+3tQO59KtJJRI9rEzgg7igz3z/egZ6paJdGGwW4eBXy7pGeXUdwT6A5qwebPjJrcOr9TvbWZQ2Onr+Gi2nIJHcj7+vyqigOuRk+vtxQAqEk4BU0ABj7j96CzzKxYD0GeM0CQG3OMAjkfOgbSZwzE4PJyfWi6caTdzaffW95akrPFIrLg/tRHpGzs9C6t0W31FrO3Y43MrcbH9c/eloZ6v0JpWoKlrHHBbScSFEHYc5Pz71NDXUoJrK1g0dvw9qsspW3nXaN6KMrHnH5ieSfan0U3Rr1uidaRbiwk8BUSS6naQkjc3ZcHaRnn70wbja6lZX+nw3NvMksM+FXnPJ9DUCeoXj2hSG2t2km7op4U/f/FAvHaNePb3N0jRzRA7VD8Akc9u/FAvcxnawZQ3HYtjJoKfDFAdeub6Vo1dSULIBtTbgYOfU8jNWUVvrm5ih0m1urixhlsI5HJliOwR5/LkkHHJPamjHdQ0HWdemlutN0+YWBYtC0rHDhjwVz3zWgx1n4e9U6QE8XT5Zd//APR5se9XBXbjS9S0zAvbO5tyWKAOhG4/KpQ3ZHXO5JFK98qRUGhfCbph77Uvx91pv463wVjR0LR7s483796WjW7rTrXpHWrSW2YK7lmXTbaIFpCRjjHOOSeeBipaNLtXuIre3R43lnkGXYADZnnmoH6Dkbzn6UDGWe9a/hKG3jsW8riQMJS3svp86B6zgMQmDtGT8qDNb6XUpOoPx72tzOkjFYowOduDwDjj70Gg6Wsq2KNeAJKRuKk52fIn5DvVkENrvW+iaSAsl0txI2Asdud5Yk4A4pgzv4l9ST6JZSXbyyprWpw+FFa5G21gz5icfzH3pgwCSQlh688+tUEwjjngZ7UHAHuWAHpn+1AXj5frQWXOGBZcKSe3c/rQIyAtnI27eBj/ADQIMAuH8vHBB9DQwVpPLjOckEZ/ahi9/Czqj/S9VhtLm6aG1uZFUsT5VOfX5Gpg9GiNJArxsrxsv1BHypYGF7pljeG3kvLZSlqzNGGxhSRjP6GoG1yLUWiWc2nSPA4KJGItyYHYHHarop3wu0jWYNUvzriNBp8ErraRMANxJ/N7nA7ZqDUHgSQLvAbacjI7H3oOuIFuYzGS68jJRyp4+lA0m0yDwGjiTw3bzBwTuDe+TQVbV+mLmW1NtbSok9weZiC2zPLEZ+/FBM6Xo40/TYdL8Jr21G4vJcuCck55HbFWUKQ/h4tR/DTz2o8TK21qmMgKOf8AfpmrokljG1i5BHI57D5VNorut9Lab1LA638W6H8sboNrqQckq3pntV0RWsfD6K7SGC3vTFahQJY2iVmkI9d+Mimie0Hp2DQ7AQacio3JZgqjcT3zxk1KHGldPWtnqMupS5uNTmGGnk5KjGNqf0r8qgmkhVGcquGblm96BDUZZYLGVrdN8+MIvux7UGKTdXdbaRrFvbaxbWN4d58BmwCjHPORycLx2q4LNe9S9TdN6I13qkWmzSXdwBCGlO4hiMKAB2A9ag0WySQwpLLtMjDcQBhVz6CgoHxF17XbnUYunulgsUsu4TTvjIUAEhR+x4qwZwtkOi7651PXJobm4tohHbQhdgecjnaPZeOfeqMy1vWLvWNQlvb+ZpJpWyT2A9gB6Cgjy5AO4A5oAGRgBR39aA7Z8MkFtxPY0AbV9UGfpQWhj5TkBQGxuBoEGG1iQCyHvj1oELgSkK6oRnIBIxzRdJ28Q3+fHiAds96LoH3AF1wCfyijNbF8JviI1rbQ6Pq/iSopxFOx5Uf0n3qUbWQk8II2SRyDPuCDUHMpSIiJQSBwDwKAgTxApnEbyIQ+APyn0+9A5B3AgfmoEWgcb3VlMpGFYjt+negSs7zxH/C3RWO9UElM8SAHG5fl/agNdXcEbJAZ1WadvDQDJO7Gf7c0ED1dqWv2enzw6Rb24nZfJd3EwREHqxyMZHzOKBbT7H8PZWTK5uZ9o3Xm1SzEry5PsT7UFF+JnUezSZ9LttRs2km2m5KSFWXDZI491AyBzVwK6J8T7CRtPjee0tbaGAtdNISdoXgLEo5JJxyfSmC6aF1fo2vELZXDJOxwkMybHYe4HtUFiJWJd8rKqjuTQcZV8SNI0dy43BlGVA+ZoBniE0RU7tp77Tg5zQUv4hNrU2tdNWOhylPEnaS5UHGYlAzn5cn74oHGt6l0z07k6nJC123HhKPFlbPptGTj9q0Kx0XMvU+ty6vqQtpWlZo4LOdGDWsak8Aflycgk+v2qC8a1q8OnaXLPOz2kCIWkZ+CqjgYx6n0xTBkmp9Sabp0KdRyI5vJkaGw08MVKIDw8jA557896QY1q2o3eqXr3N7O8skjnlnzgn5e1UMCGV/MOM0BJFOVwfX0oFtgZTjkg8UBtpOeO1B3hg85FBZXVMM+VJAA2+h96BO4IMJ/p7qvuKBKacmOKB5CYYx5UzgDPfHzoGwD5OApJHAHrQEAk8NWdNpx+XdkA0AIGhkGWOQcgg8UGw/DP4kmwhi07WCTZqAiSbstGc4+pFKNvs5o7q2Sa3kWaJxkOp4NZDOHUh/qL2k8LW78eG7kbZv+0+/yoEZp7fUpX/BXpgvYZTCSRtO7vtwe/vQdY6jeyatPp91FEPw8aSNMoYbi2cADt6Z70DS60KW7luJdV1JniJzBtURG2b0KN7+/vQKSWUWnLLqN3cSLP4ex5Y8jxiPykr23+nzzigpXUPVOu6Vqmmf8UWttb9OXDqkjRnfI3H849uRkDOKC0axLFr+nLB0rrUMM0bqCIGGGX1AH09qsGc9UfBiTV9Vhu9Pu5oPGLNeG6bczN7jHvVEr058Gre3sLeDVrmOdo3LmSFNjEH+XdntQXO51XQOl5YrCKGWa8SMYS3tzMyLjjJHb9alDqz1S5ktJ7nVdLmSVDiOONfEMiE4Xy+h9xUDm11CaTxEOn3VmpHFxKFCr9s5GPmKAus6jb9M6RJf3c88yxpjcxL7uM5OO3HrQVTSupoOuYdZMTSpptriNFtXKXDA/Pjhs9h2xQOJ7Xpnpa2S91WK2swqjbGw3ysfcnuxrQsGmapYvpwvra1FtDL52Mi+Gx49sZoMb+LXV0t+jWl3OYLGTO2zjx4h2nyszHsG4/Sgxt5ZJmEsjl3PB3GgSlyXBxkDnNADseB2PsaA8SoXQyFgmQCV70B5R/EIjYmPJxnvigEKcYDfrQF2/X9aCwqC7l2zwfT/FAJJ5747E5oGTqZArKOfccftQHZWwmOD23Z4NAEkTEBmwR7g5AoG7KSSE5HyFAMTyQsMHa/cEcEc5oL58P+v7rppdryPNAXx+GfsQe7Z9D2/Wg3zSdX0fqzT08F433eYwscOpHt9PcVkQPW632mX9vfWdrbXiRgrIdu2eHIwGD57+nIoKdc/ELVdC0u5afp27SUtta5vJMMzk+UDjzYHtQWDpj4gxXmif/wAitXZkGZzFGW8MehZO+PmM0Fibr/poWQmF6xXA2xmFg59sKRk0C2nQP1KFvdb0vwIUJNtDKcsVP8zD0Jx2oJDTNA0vR5p7qzs44pJOXkUc/SgNfa/pNvbF5L2JgTsCo2WJzjGKA1jcNcxOF/m/I0zbt4+gxgenNA5s7CCxWWYQxpNLgyMiY3nt2oHajcuexAoEL1C1uyFkVHO1ixHb17/KgwT4rdXWep6oul2OpywaTYqVLxDyySDjaM9x6Z+tWDPdB1TW7Wa9sumpGlursqMQRlpXwd3BA4571RcdN0i41G7h/wBSmNxqdkwn1O6u5/4cAXlYgcnngE/pQNvih8S211obHRyYbWInfJG/Ex9MD2+tBmNzcTXTtJcSSSSHH5jngDAH0oEdxbg5A9wKAzPwO+fegSLfLJoFoR5fUfegXOcHGAT8qAM+XaBzQCCwGDuyPlQWJpV37Q5TIweM7u/f9qA9vNYpFML2KaR8YiaJgAh55PvQRvnYoqA+MThcDnPai4PKWQlH3K6tggjnPaiEmz4ZznBPfFAVWG0AZDH1z2HzoE7lhv8AJIHI/mGRQI8AEeuOMGgndN6pu7V4RJLKY4WDLhypXj0oNL6d+MMS4ttetDdQgDNwAPEwPRh2NZGkabrvTXVZiexvba5aI+ILWZQG3Y4IDdvtQScvTdjK8chtFjkQ+VlYgqPXGKA17daV07apJrV9CsZbELTgbu3YY78UEHf9evJ4K9P6JqGoiR1XxjCUjAJ5OT3NBM9YdSWPTenwy3t7bWbSuBunUthfUhRyT+1BA2vXnS/jGdeo9LnIHljeLwSCe5zgmgejrOz1S3kGhazoaXYGAJ5Sw3e38uaCsJfX02rPD1XfXtvcCXdBJGjLbOO+EK88Y7nIoLB1H1Bb6WkN1ddSQ29io/5MZEjzt7DGTjj2FXNGUfEH4wRaxCtnp2kwGGM7llvBvIOO4XOAe/fNMwZbqusalfLBHfzSvFH+SIgKo+igYqiwWfWV30rpp03p6exJnUPJexQnxuR+Ulu2PkKCrT6jcSiTxZnbxCWcFidxPJJ96BBDlQ35fbFAbahBHJIGO+KAIwg5YnB455oDkKcbW7UAOowSMjOORQcCVXPp+9AqDkHcDmgMNpHPcUBTuzQWCJXcFvKR2Y0CMiqjnz4UcH/6oG8gKluwxyAfSjQ6ylEJBJfv37/OiYQMjbjkZXOSP/FEELAEkNn1waBCXdjORnPoc80CZeTb5wQe2BQAm4y7jlhjvQcWO3cW4GB7ZpgGC5a3uUeNyGQ5GCR+45pgt+l/EzqLTgxj1O5Zc4CSOXCj70wOE+Jd/Pq0V7qVvb3bISAWUBhnuc+/2pgvkHx0soLaNIdKkEiqR5yDg47cYpgresfELSNc1n8VrFtAw2ZBiiywwcgeb14x2xTBYNA13ozUo/GOqWVizDc1nf6crIh/7wOf1rOURvVupdE6ncpFeakiSWsZdbjSLfw1Zs+VVyMHA75xWsFDHU0idTJdf65rT28YKpPvHjKp9Bk49qYK/rGpXF/qU9zPdyzyyMSJJAAx9ifnVlwNZ7vxYEh8GAEHO8DDH5H5U0IPK8jHxSzFQAMnOKgJkFwPT6UBlAII5z3zQCjnA5OKBXeuAT9KABMA208DtxQHRhzgUC3KjJx9z2oAP6/L3NAHC8Hg/XNAcNtGe4oEy5yeaCdLk7yx2qQCAO1AmXZSSexHbPNAhJuLJkgjvzRonuAJy2cd8UCbyOi453Dj7GiYTZyVPPl74oYLJIyq68EH3Gf3oYTDEjLbiP1FEDHOUOdgOfXIBFAm77j5Mnng/WgLI5UE8Eg9iO9AnuJbuQx5wOBQFRxuIbOc54PrQK28ws76F722EyI4d4HJUOPb35yKBm8oeQsi4BPbPb71RyYIHmPGRg00GRsbsHIPY0Bg52AEEseBUCQJyOPXtQDtcdvvjtQCQ/GBwKAuXU4PrQBvZE5IGeO1AffjBJ57UBvEO045HagFWAAzktQKIzBeMg0C5kz5mOG/WgMrDJJ7jmgEnIyOccYoA3cEMRj05oC7/wDeBQTduzEoNxwcZGaAJOWfPNAlISVOT60aIQfkj+amgJ3bnnigKeFGPQUCf/x0Smw4V8exogX/AOY3+/SgKxKxeU459KAgJOckntQJkkcgkGgAAFFz/XQEmJaY7jnk96BM9yPQelAf/wCX7UBv/jagGP8AKB6ZoDf00HMfO/0oAH5TQA/5moECSMDPFAvGASMjPP8AigVX+b60BW7/AHoHEJJD55oDd4snv70CsSjCcDmgVAAbgYoGYJ3nk9qBUAYHAoP/2Q==
\ No newline at end of file
diff --git a/tests/writer.html b/tests/writer.html
index b0227e21b..e8e619f44 100644
--- a/tests/writer.html
+++ b/tests/writer.html
@@ -324,7 +324,6 @@ These should not be escaped: \$ \\ \> \[ \{
foo
-
And nested without indentation:
@@ -336,7 +335,6 @@ foo
bar
-
Interpreted markdown in a table:
@@ -353,10 +351,8 @@ And this is strong
Here’s a simple block:
-
foo
-
This should be a code block, though:
<div>
foo
@@ -365,14 +361,12 @@ foo
<div>foo</div>
Now, nested:
-
This should just be an HTML comment:
diff --git a/tests/writer.markdown b/tests/writer.markdown
index 2201ac8d1..7d67e4e87 100644
--- a/tests/writer.markdown
+++ b/tests/writer.markdown
@@ -356,20 +356,31 @@ HTML Blocks
Simple block on one line:
+
foo
+
And nested without indentation:
Interpreted markdown in a table:
@@ -390,8 +401,9 @@ And this is **strong**
Here’s a simple block:
-
+
foo
+
This should be a code block, though:
@@ -407,12 +419,17 @@ As should this:
Now, nested:
-
This should just be an HTML comment:
diff --git a/tests/writer.mediawiki b/tests/writer.mediawiki
index 7eccc44e8..2f3726285 100644
--- a/tests/writer.mediawiki
+++ b/tests/writer.mediawiki
@@ -311,22 +311,30 @@ Blank line after term, indented marker, alternate markers:
Simple block on one line:
+
foo
-
+
And nested without indentation:
+
Interpreted markdown in a table:
@@ -345,10 +353,10 @@ And this is '''strong'''
Here’s a simple block:
-
+
foo
-
+
This should be a code block, though:
<div>
@@ -360,14 +368,18 @@ As should this:
Now, nested:
-
This should just be an HTML comment:
diff --git a/tests/writer.native b/tests/writer.native
index d1b14b24e..678d7595f 100644
--- a/tests/writer.native
+++ b/tests/writer.native
@@ -228,15 +228,9 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Plain [Str "sublist"]]]]])]
,Header 1 ("html-blocks",[],[]) [Str "HTML",Space,Str "Blocks"]
,Para [Str "Simple",Space,Str "block",Space,Str "on",Space,Str "one",Space,Str "line:"]
-,RawBlock (Format "html") "
"
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n"
+,Div ("",[],[]) [Plain [Str "foo"]]
,Para [Str "And",Space,Str "nested",Space,Str "without",Space,Str "indentation:"]
-,RawBlock (Format "html") "
\n
\n
"
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n
\n
"
-,Plain [Str "bar"]
-,RawBlock (Format "html") "
\n
\n"
+,Div ("",[],[]) [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "foo"]]],Div ("",[],[]) [Plain [Str "bar"]]]
,Para [Str "Interpreted",Space,Str "markdown",Space,Str "in",Space,Str "a",Space,Str "table:"]
,RawBlock (Format "html") "
\n\n| "
,Plain [Str "This",Space,Str "is",Space,Emph [Str "emphasized"]]
@@ -244,17 +238,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Plain [Str "And",Space,Str "this",Space,Str "is",Space,Strong [Str "strong"]]
,RawBlock (Format "html") " | \n
\n
\n\n\n"
,Para [Str "Here\8217s",Space,Str "a",Space,Str "simple",Space,Str "block:"]
-,RawBlock (Format "html") "
\n "
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n"
+,Div ("",[],[]) [Plain [Str "foo"]]
,Para [Str "This",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "code",Space,Str "block,",Space,Str "though:"]
,CodeBlock ("",[],[]) "
\n foo\n
"
,Para [Str "As",Space,Str "should",Space,Str "this:"]
,CodeBlock ("",[],[]) "
foo
"
,Para [Str "Now,",Space,Str "nested:"]
-,RawBlock (Format "html") "
\n
\n
\n "
-,Plain [Str "foo"]
-,RawBlock (Format "html") "
\n
\n
\n"
+,Div ("",[],[]) [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "foo"]]]]
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
,RawBlock (Format "html") "\n"
,Para [Str "Multiline:"]
diff --git a/tests/writer.opml b/tests/writer.opml
index b0954a439..228cad247 100644
--- a/tests/writer.opml
+++ b/tests/writer.opml
@@ -44,7 +44,7 @@
-
+
diff --git a/tests/writer.org b/tests/writer.org
index b8058a406..85016f352 100644
--- a/tests/writer.org
+++ b/tests/writer.org
@@ -359,7 +359,13 @@ And nested without indentation:
#+BEGIN_HTML
+#+END_HTML
+
+#+BEGIN_HTML
+#+END_HTML
+
+#+BEGIN_HTML
#+END_HTML
@@ -367,7 +373,13 @@ foo
#+BEGIN_HTML
+#+END_HTML
+
+#+BEGIN_HTML
+#+END_HTML
+
+#+BEGIN_HTML
#+END_HTML
@@ -375,6 +387,9 @@ bar
#+BEGIN_HTML
+#+END_HTML
+
+#+BEGIN_HTML
#+END_HTML
@@ -407,7 +422,6 @@ Here's a simple block:
#+BEGIN_HTML
-
#+END_HTML
foo
@@ -434,16 +448,27 @@ Now, nested:
#+BEGIN_HTML
-
-
-
+#+END_HTML
+
+#+BEGIN_HTML
+
+#+END_HTML
+
+#+BEGIN_HTML
+
#+END_HTML
foo
#+BEGIN_HTML
-
+#+END_HTML
+
+#+BEGIN_HTML
+
+#+END_HTML
+
+#+BEGIN_HTML
#+END_HTML
diff --git a/tests/writer.plain b/tests/writer.plain
index cc61916d2..60e7bb329 100644
--- a/tests/writer.plain
+++ b/tests/writer.plain
@@ -352,10 +352,13 @@ HTML Blocks
Simple block on one line:
foo
+
And nested without indentation:
foo
+
bar
+
Interpreted markdown in a table:
This is emphasized
@@ -363,6 +366,7 @@ And this is strong
Here’s a simple block:
foo
+
This should be a code block, though:
@@ -376,6 +380,7 @@ As should this:
Now, nested:
foo
+
This should just be an HTML comment:
Multiline:
diff --git a/tests/writer.rst b/tests/writer.rst
index 41da5bc73..68bc4a06c 100644
--- a/tests/writer.rst
+++ b/tests/writer.rst
@@ -394,7 +394,13 @@ And nested without indentation:
.. raw:: html
+
+.. raw:: html
+
+
+.. raw:: html
+
foo
@@ -402,7 +408,13 @@ foo
.. raw:: html
+
+.. raw:: html
+
+
+.. raw:: html
+
bar
@@ -410,6 +422,9 @@ bar
.. raw:: html
+
+.. raw:: html
+
Interpreted markdown in a table:
@@ -442,7 +457,6 @@ Here’s a simple block:
.. raw:: html
-
foo
@@ -469,16 +483,27 @@ Now, nested:
.. raw:: html
-
-
-
+
+.. raw:: html
+
+
+
+.. raw:: html
+
+
foo
.. raw:: html
-
+
+.. raw:: html
+
+
+
+.. raw:: html
+
This should just be an HTML comment:
diff --git a/tests/writer.textile b/tests/writer.textile
index 31789a2b0..5042f79cb 100644
--- a/tests/writer.textile
+++ b/tests/writer.textile
@@ -352,20 +352,33 @@ h1(#html-blocks). HTML Blocks
Simple block on one line:
+
foo
+
And nested without indentation:
Interpreted markdown in a table:
@@ -386,8 +399,9 @@ And this is *strong*
Here's a simple block:
-
+
foo
+
This should be a code block, though:
@@ -405,12 +419,19 @@ bc.
foo
Now, nested:
-
This should just be an HTML comment:
--
cgit v1.2.3
From e8ddcfd997bd1733b715a4321f0e57c7860071d2 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Mon, 19 Aug 2013 16:03:22 -0700
Subject: Scale LaTeX tables so they don't exceed columnwidth.
---
src/Text/Pandoc/Writers/LaTeX.hs | 6 +++-
tests/tables.latex | 64 ++++++++++++++++++++--------------------
2 files changed, 37 insertions(+), 33 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 98553c421..ab579a326 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -470,9 +470,13 @@ tableRowToLaTeX header aligns widths cols = do
AlignRight -> "\\raggedleft"
AlignCenter -> "\\centering"
AlignDefault -> "\\raggedright"
+ -- scale factor compensates for extra space between columns
+ -- so the whole table isn't larger than columnwidth
+ let scaleFactor = 0.97 ** fromIntegral (length aligns)
let toCell 0 _ c = c
toCell w a c = "\\begin{minipage}" <> valign <>
- braces (text (printf "%.2f\\columnwidth" w)) <>
+ braces (text (printf "%.2f\\columnwidth"
+ (w * scaleFactor))) <>
(halign a <> cr <> c <> cr) <> "\\end{minipage}"
let cells = zipWith3 toCell widths aligns renderedCells
return $ hsep (intersperse "&" cells) $$ "\\\\\\noalign{\\medskip}"
diff --git a/tests/tables.latex b/tests/tables.latex
index 82abeb9a5..c27e10461 100644
--- a/tests/tables.latex
+++ b/tests/tables.latex
@@ -54,34 +54,34 @@ Multiline table with caption:
\begin{longtable}[c]{@{}clrl@{}}
\hline\noalign{\medskip}
-\begin{minipage}[b]{0.15\columnwidth}\centering
+\begin{minipage}[b]{0.13\columnwidth}\centering
Centered Header
-\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright
Left Aligned
-\end{minipage} & \begin{minipage}[b]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft
Right Aligned
-\end{minipage} & \begin{minipage}[b]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright
Default aligned
\end{minipage}
\\\noalign{\medskip}
\hline\noalign{\medskip}
-\begin{minipage}[t]{0.15\columnwidth}\centering
+\begin{minipage}[t]{0.13\columnwidth}\centering
First
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
row
-\end{minipage} & \begin{minipage}[t]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
12.0
-\end{minipage} & \begin{minipage}[t]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
Example of a row that spans multiple lines.
\end{minipage}
\\\noalign{\medskip}
-\begin{minipage}[t]{0.15\columnwidth}\centering
+\begin{minipage}[t]{0.13\columnwidth}\centering
Second
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
row
-\end{minipage} & \begin{minipage}[t]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
5.0
-\end{minipage} & \begin{minipage}[t]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
Here's another one. Note the blank line between rows.
\end{minipage}
\\\noalign{\medskip}
@@ -94,34 +94,34 @@ Multiline table without caption:
\begin{longtable}[c]{@{}clrl@{}}
\hline\noalign{\medskip}
-\begin{minipage}[b]{0.15\columnwidth}\centering
+\begin{minipage}[b]{0.13\columnwidth}\centering
Centered Header
-\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright
Left Aligned
-\end{minipage} & \begin{minipage}[b]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft
Right Aligned
-\end{minipage} & \begin{minipage}[b]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright
Default aligned
\end{minipage}
\\\noalign{\medskip}
\hline\noalign{\medskip}
-\begin{minipage}[t]{0.15\columnwidth}\centering
+\begin{minipage}[t]{0.13\columnwidth}\centering
First
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
row
-\end{minipage} & \begin{minipage}[t]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
12.0
-\end{minipage} & \begin{minipage}[t]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
Example of a row that spans multiple lines.
\end{minipage}
\\\noalign{\medskip}
-\begin{minipage}[t]{0.15\columnwidth}\centering
+\begin{minipage}[t]{0.13\columnwidth}\centering
Second
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
row
-\end{minipage} & \begin{minipage}[t]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
5.0
-\end{minipage} & \begin{minipage}[t]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
Here's another one. Note the blank line between rows.
\end{minipage}
\\\noalign{\medskip}
@@ -145,23 +145,23 @@ Multiline table without column headers:
\begin{longtable}[c]{@{}clrl@{}}
\hline\noalign{\medskip}
-\begin{minipage}[t]{0.15\columnwidth}\centering
+\begin{minipage}[t]{0.13\columnwidth}\centering
First
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
row
-\end{minipage} & \begin{minipage}[t]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
12.0
-\end{minipage} & \begin{minipage}[t]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
Example of a row that spans multiple lines.
\end{minipage}
\\\noalign{\medskip}
-\begin{minipage}[t]{0.15\columnwidth}\centering
+\begin{minipage}[t]{0.13\columnwidth}\centering
Second
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
row
-\end{minipage} & \begin{minipage}[t]{0.16\columnwidth}\raggedleft
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
5.0
-\end{minipage} & \begin{minipage}[t]{0.34\columnwidth}\raggedright
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
Here's another one. Note the blank line between rows.
\end{minipage}
\\\noalign{\medskip}
--
cgit v1.2.3
From 7048c130ec9d128dd1c9d1ddf8e7ce3c15eaf435 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 18 Aug 2013 23:01:23 -0700
Subject: Create Cite element even if no matching reference in the biblio.
* Add ??? as fallback text for non-resolved citations.
* Biblio: Put references (including a header at the end of
the document, if one exists) inside a Div with class "references".
This gives some control over styling of references, and allows
scripts to manipulate them.
* Markdown writer: Print markdown citation codes, and disable
printing of references, if `citations` extension is enabled.
NOTE: It would be good to improve what citeproc-hs does for
a nonexistent key.
---
src/Text/Pandoc/Biblio.hs | 5 +-
src/Text/Pandoc/Readers/Markdown.hs | 21 ++++----
src/Text/Pandoc/Writers/Markdown.hs | 35 +++++++------
tests/Tests/Old.hs | 2 +-
tests/markdown-citations.chicago-author-date.txt | 10 +++-
tests/markdown-citations.ieee.txt | 40 ++++++++-------
tests/markdown-citations.mhra.txt | 62 ++++++++++++++----------
7 files changed, 105 insertions(+), 70 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs
index 206b38530..1c0975f11 100644
--- a/src/Text/Pandoc/Biblio.hs
+++ b/src/Text/Pandoc/Biblio.hs
@@ -55,7 +55,10 @@ processBiblio (Just style) r p =
cits_map = M.fromList $ zip grps (citations result)
biblioList = map (renderPandoc' style) (bibliography result)
Pandoc m b = bottomUp mvPunct . deNote . topDown (processCite style cits_map) $ p'
- in Pandoc m $ b ++ biblioList
+ (bs, lastb) = case reverse b of
+ x@(Header _ _ _) : xs -> (reverse xs, [x])
+ _ -> (b, [])
+ in Pandoc m $ bs ++ [Div ("",["references"],[]) (lastb ++ biblioList)]
-- | Substitute 'Cite' elements with formatted citations.
processCite :: Style -> M.Map [Citation] [FormattedOutput] -> Inline -> Inline
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index a653c2e98..05662d9b5 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -55,7 +55,6 @@ import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag,
isTextTag, isCommentTag )
import Text.Pandoc.Biblio (processBiblio)
-import qualified Text.CSL as CSL
import Data.Monoid (mconcat, mempty)
import Control.Applicative ((<$>), (<*), (*>), (<$))
import Control.Monad
@@ -1797,11 +1796,13 @@ rawHtmlInline = do
cite :: MarkdownParser (F Inlines)
cite = do
guardEnabled Ext_citations
- getOption readerReferences >>= guard . not . null
- citations <- textualCite <|> normalCite
- return $ flip B.cite mempty <$> citations
+ citations <- textualCite <|> (fmap (flip B.cite unknownC) <$> normalCite)
+ return citations
+
+unknownC :: Inlines
+unknownC = B.str "???"
-textualCite :: MarkdownParser (F [Citation])
+textualCite :: MarkdownParser (F Inlines)
textualCite = try $ do
(_, key) <- citeKey
let first = Citation{ citationId = key
@@ -1813,8 +1814,12 @@ textualCite = try $ do
}
mbrest <- option Nothing $ try $ spnl >> Just <$> normalCite
case mbrest of
- Just rest -> return $ (first:) <$> rest
- Nothing -> option (return [first]) $ bareloc first
+ Just rest -> return $ (flip B.cite unknownC . (first:)) <$> rest
+ Nothing -> (fmap (flip B.cite unknownC) <$> bareloc first) <|>
+ return (do st <- askF
+ return $ case M.lookup key (stateExamples st) of
+ Just n -> B.str (show n)
+ _ -> B.cite [first] unknownC)
bareloc :: Citation -> MarkdownParser (F [Citation])
bareloc c = try $ do
@@ -1846,8 +1851,6 @@ citeKey = try $ do
let internal p = try $ p >>~ lookAhead (letter <|> digit)
rest <- many $ letter <|> digit <|> internal (oneOf ":.#$%&-_+?<>~/")
let key = first:rest
- citations' <- map CSL.refId <$> getOption readerReferences
- guard $ key `elem` citations'
return (suppress_author, key)
suffix :: MarkdownParser (F Inlines)
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 623c445df..d617954dd 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -186,7 +186,12 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
let toc = if writerTableOfContents opts
then tableOfContents opts headerBlocks
else empty
- body <- blockListToMarkdown opts blocks
+ -- Strip off final 'references' header if markdown citations enabled
+ let blocks' = case reverse blocks of
+ (Div (_,["references"],_) _):xs
+ | isEnabled Ext_citations opts -> reverse xs
+ _ -> blocks
+ body <- blockListToMarkdown opts blocks'
st <- get
notes' <- notesToMarkdown opts (reverse $ stNotes st)
st' <- get -- note that the notes may contain refs
@@ -304,10 +309,10 @@ blockToMarkdown _ Null = return empty
blockToMarkdown opts (Div attrs ils) = do
isPlain <- gets stPlain
contents <- blockListToMarkdown opts ils
- return $ if isPlain
+ return $ if isPlain || not (isEnabled Ext_markdown_in_html_blocks opts)
then contents <> blankline
else tagWithAttrs "div" attrs <> blankline <>
- contents <> blankline <> "" <> blankline
+ contents <> blankline <> "
" <> blankline
blockToMarkdown opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
return $ contents <> cr
@@ -711,17 +716,20 @@ inlineToMarkdown opts (LineBreak)
| isEnabled Ext_escaped_line_breaks opts = return $ "\\" <> cr
| otherwise = return $ " " <> cr
inlineToMarkdown _ Space = return space
-inlineToMarkdown opts (Cite (c:cs) lst@[RawInline "latex" _])
+inlineToMarkdown opts (Cite [] lst) = inlineListToMarkdown opts lst
+inlineToMarkdown opts (Cite (c:cs) lst)
| not (isEnabled Ext_citations opts) = inlineListToMarkdown opts lst
- | citationMode c == AuthorInText = do
- suffs <- inlineListToMarkdown opts $ citationSuffix c
- rest <- mapM convertOne cs
- let inbr = suffs <+> joincits rest
- br = if isEmpty inbr then empty else char '[' <> inbr <> char ']'
- return $ text ("@" ++ citationId c) <+> br
- | otherwise = do
- cits <- mapM convertOne (c:cs)
- return $ text "[" <> joincits cits <> text "]"
+ | otherwise =
+ if citationMode c == AuthorInText
+ then do
+ suffs <- inlineListToMarkdown opts $ citationSuffix c
+ rest <- mapM convertOne cs
+ let inbr = suffs <+> joincits rest
+ br = if isEmpty inbr then empty else char '[' <> inbr <> char ']'
+ return $ text ("@" ++ citationId c) <+> br
+ else do
+ cits <- mapM convertOne (c:cs)
+ return $ text "[" <> joincits cits <> text "]"
where
joincits = hcat . intersperse (text "; ") . filter (not . isEmpty)
convertOne Citation { citationId = k
@@ -738,7 +746,6 @@ inlineToMarkdown opts (Cite (c:cs) lst@[RawInline "latex" _])
return $ pdoc <+> r
modekey SuppressAuthor = "-"
modekey _ = ""
-inlineToMarkdown opts (Cite _ lst) = inlineListToMarkdown opts lst
inlineToMarkdown opts (Link txt (src, tit)) = do
linktext <- inlineListToMarkdown opts txt
let linktitle = if null tit
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index 0ba240084..8609781d0 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -196,7 +196,7 @@ markdownCitationTests
++ [test "natbib" wopts "markdown-citations.txt"
"markdown-citations.txt"]
where
- ropts = ["-r", "markdown", "-w", "markdown", "--bibliography",
+ ropts = ["-r", "markdown", "-w", "markdown-citations", "--bibliography",
"biblio.bib", "--no-wrap"]
wopts = ["-r", "markdown", "-w", "markdown", "--no-wrap", "--natbib"]
styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"])
diff --git a/tests/markdown-citations.chicago-author-date.txt b/tests/markdown-citations.chicago-author-date.txt
index de242300d..81d7482cb 100644
--- a/tests/markdown-citations.chicago-author-date.txt
+++ b/tests/markdown-citations.chicago-author-date.txt
@@ -1,9 +1,9 @@
Pandoc with citeproc-hs
=======================
-- [@nonexistent]
+- ([CSL BIBLIOGRAPHIC DATA ERROR: reference "nonexistent" not found.])
-- @nonexistent
+- ([CSL BIBLIOGRAPHIC DATA ERROR: reference "nonexistent" not found.])
- Doe (2005) says blah.
@@ -29,15 +29,21 @@ Pandoc with citeproc-hs
- With some markup (*see* Doe 2005, 32).
+
+
References
==========
+“Nonexistent Not Found!”
+
Doe, John. 2005. *First Book*. Cambridge: Cambridge University Press.
———. 2006. “Article.” *Journal of Generic Studies* 6: 33–34.
Doe, John, and Jenny Roe. 2007. “Why Water Is Wet.” In *Third Book*, edited by Sam Smith. Oxford: Oxford University Press.
+
+
[^1]: Doe and Roe (2007, 12) and a citation without locators (Doe and Roe 2007).
[^2]: Some citations (see Doe 2005, chap. 3; Doe and Roe 2007; Doe 2006).
diff --git a/tests/markdown-citations.ieee.txt b/tests/markdown-citations.ieee.txt
index a397e3f38..4085a7c63 100644
--- a/tests/markdown-citations.ieee.txt
+++ b/tests/markdown-citations.ieee.txt
@@ -1,45 +1,51 @@
Pandoc with citeproc-hs
=======================
-- [@nonexistent]
+- []
-- @nonexistent
+-
-- Reference 1 says blah.
+- Reference 2 says blah.
-- Reference 1 says blah.
+- Reference 2 says blah.
-- Reference 1 says blah.
+- Reference 2 says blah.
-- Reference 1 [3] says blah.
+- Reference 2 [4] says blah.
- In a note.[^1]
-- A citation group [1], [3].
+- A citation group [2], [4].
-- Another one [1].
+- Another one [2].
- And another one in a note.[^2]
-- Citation with a suffix and locator [1].
+- Citation with a suffix and locator [2].
-- Citation with suffix only [1].
+- Citation with suffix only [2].
- Now some modifiers.[^3]
-- With some markup [1].
+- With some markup [2].
+
+
References
==========
-[1] J. Doe, *First Book*. Cambridge: Cambridge University Press, 2005.
+[1]“nonexistent not found!” .
+
+[2] J. Doe, *First Book*. Cambridge: Cambridge University Press, 2005.
+
+[3] J. Doe, “Article,” *Journal of Generic Studies*, vol. 6, pp. 33–34, 2006.
-[2] J. Doe, “Article,” *Journal of Generic Studies*, vol. 6, pp. 33–34, 2006.
+[4] J. Doe and J. Roe, “Why Water Is Wet,” in *Third Book*, S. Smith, Ed. Oxford: Oxford University Press, 2007.
-[3] J. Doe and J. Roe, “Why Water Is Wet,” in *Third Book*, S. Smith, Ed. Oxford: Oxford University Press, 2007.
+
-[^1]: Reference 3 and a citation without locators [3].
+[^1]: Reference 4 and a citation without locators [4].
-[^2]: Some citations [1–3].
+[^2]: Some citations [2–4].
-[^3]: Like a citation without author: [1], and now Doe with a locator [2].
+[^3]: Like a citation without author: [2], and now Doe with a locator [3].
diff --git a/tests/markdown-citations.mhra.txt b/tests/markdown-citations.mhra.txt
index d33a1b94b..01d9c45ca 100644
--- a/tests/markdown-citations.mhra.txt
+++ b/tests/markdown-citations.mhra.txt
@@ -1,33 +1,35 @@
Pandoc with citeproc-hs
=======================
-- [@nonexistent]
+- [^1]
-- @nonexistent
+- [^2]
-- John Doe[^1] says blah.
+- John Doe[^3] says blah.
-- Doe[^2] says blah.
+- Doe[^4] says blah.
-- Doe[^3] says blah.
+- Doe[^5] says blah.
-- Doe[^4] says blah.
+- Doe[^6] says blah.
-- In a note.[^5]
+- In a note.[^7]
-- A citation group.[^6]
+- A citation group.[^8]
-- Another one.[^7]
+- Another one.[^9]
-- And another one in a note.[^8]
+- And another one in a note.[^10]
-- Citation with a suffix and locator.[^9]
+- Citation with a suffix and locator.[^11]
-- Citation with suffix only.[^10]
+- Citation with suffix only.[^12]
-- Now some modifiers.[^11]
+- Now some modifiers.[^13]
-- With some markup.[^12]
+- With some markup.[^14]
+
+
References
==========
@@ -38,26 +40,34 @@ Doe, John, ‘Article’, *Journal of Generic Studies*, 6 (2006), 33–34.
Doe, John, and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed. by Sam Smith (Oxford: Oxford University Press, 2007).
-[^1]: *First Book* (Cambridge: Cambridge University Press, 2005).
+‘Nonexistent Not Found!’.
+
+
+
+[^1]: [CSL BIBLIOGRAPHIC DATA ERROR: reference "nonexistent" not found.].
+
+[^2]: [CSL STYLE ERROR: reference with no printed form.].
+
+[^3]: *First Book* (Cambridge: Cambridge University Press, 2005).
-[^2]: *First Book*, p. 30.
+[^4]: *First Book*, p. 30.
-[^3]: *First Book*, p. 30, with suffix.
+[^5]: *First Book*, p. 30, with suffix.
-[^4]: *First Book*; ‘Article’, *Journal of Generic Studies*, 6 (2006), 33–34 (p. 30); see also John Doe and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed. by Sam Smith (Oxford: Oxford University Press, 2007).
+[^6]: *First Book*; ‘Article’, *Journal of Generic Studies*, 6 (2006), 33–34 (p. 30); see also John Doe and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed. by Sam Smith (Oxford: Oxford University Press, 2007).
-[^5]: Doe and Roe, p. 12 and a citation without locators Doe and Roe.
+[^7]: Doe and Roe, p. 12 and a citation without locators Doe and Roe.
-[^6]: See Doe, *First Book*, chap. 3; also Doe and Roe, pp. 34–35.
+[^8]: See Doe, *First Book*, chap. 3; also Doe and Roe, pp. 34–35.
-[^7]: See Doe, *First Book*, pp. 34–35.
+[^9]: See Doe, *First Book*, pp. 34–35.
-[^8]: Some citations see Doe, *First Book*, chap. 3; Doe and Roe; Doe, ‘Article’, 33–34.
+[^10]: Some citations see Doe, *First Book*, chap. 3; Doe and Roe; Doe, ‘Article’, 33–34.
-[^9]: Doe, *First Book*, pp. 33, 35–37, and nowhere else.
+[^11]: Doe, *First Book*, pp. 33, 35–37, and nowhere else.
-[^10]: Doe, *First Book* and nowhere else.
+[^12]: Doe, *First Book* and nowhere else.
-[^11]: Like a citation without author: *First Book*, and now Doe with a locator ‘Article’, 33–34 (p. 44).
+[^13]: Like a citation without author: *First Book*, and now Doe with a locator ‘Article’, 33–34 (p. 44).
-[^12]: *See* Doe, *First Book*, p. 32.
+[^14]: *See* Doe, *First Book*, p. 32.
--
cgit v1.2.3
From 5f09cf7ff033ae11c5094fe39f8cd2ac11657229 Mon Sep 17 00:00:00 2001
From: Florian Eitel
Date: Thu, 22 Aug 2013 20:15:36 +0200
Subject: Write id for code block to label attr in latex when listing is used
The code:
~~~{#test}
asdf
~~~
gets compiled to html:
asdf
So it is possible to link to the identifier `test`
But this doesn't happen on latex
When using the listings package (`--listings`) it is possible to set the
identifier using the `label=test` property:
\begin{lstlisting}[label=id]
hi
\end{lstlisting}
And this is exactly what this patch is doing.
Modified LaTeX Reader/Writer and added tests for this.
---
src/Text/Pandoc/Readers/LaTeX.hs | 3 ++-
src/Text/Pandoc/Writers/LaTeX.hs | 8 ++++++--
tests/Tests/Readers/LaTeX.hs | 7 +++++++
tests/Tests/Writers/LaTeX.hs | 7 +++++++
4 files changed, 22 insertions(+), 3 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index ded57df5a..b785a9852 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -47,6 +47,7 @@ import Text.Pandoc.Builder
import Data.Char (isLetter)
import Control.Applicative
import Data.Monoid
+import Data.Maybe (fromMaybe)
import System.Environment (getEnv)
import System.FilePath (replaceExtension, (>))
import Data.List (intercalate, intersperse)
@@ -901,7 +902,7 @@ environments = M.fromList
lookup "numbers" options == Just "left" ]
++ maybe [] (:[]) (lookup "language" options
>>= fromListingsLanguage)
- let attr = ("",classes,kvs)
+ let attr = (fromMaybe "" (lookup "label" options),classes,kvs)
codeBlockWith attr <$> (verbEnv "lstlisting"))
, ("minted", do options <- option [] keyvals
lang <- grouped (many1 $ satisfy (/='}'))
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ab579a326..bf056001f 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -313,7 +313,7 @@ blockToLaTeX (BlockQuote lst) = do
_ -> do
contents <- blockListToLaTeX lst
return $ "\\begin{quote}" $$ contents $$ "\\end{quote}"
-blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
+blockToLaTeX (CodeBlock (identifier,classes,keyvalAttr) str) = do
opts <- gets stOptions
case () of
_ | isEnabled Ext_literate_haskell opts && "haskell" `elem` classes &&
@@ -344,7 +344,11 @@ blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
[ (if key == "startFrom"
then "firstnumber"
else key) ++ "=" ++ attr |
- (key,attr) <- keyvalAttr ]
+ (key,attr) <- keyvalAttr ] ++
+ (if identifier == ""
+ then []
+ else [ "label=" ++ identifier ])
+
else []
printParams
| null params = empty
diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs
index 88029b7c2..dff6e4537 100644
--- a/tests/Tests/Readers/LaTeX.hs
+++ b/tests/Tests/Readers/LaTeX.hs
@@ -55,6 +55,13 @@ tests = [ testGroup "basic"
"hi % this is a comment\nthere\n" =?> para "hi there"
]
+ , testGroup "code blocks"
+ [ "identifier" =:
+ "\\begin{lstlisting}[label=test]\\end{lstlisting}" =?> codeBlockWith ("test", [], [("label","test")]) ""
+ , "no identifier" =:
+ "\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock ""
+ ]
+
, testGroup "citations"
[ natbibCitations
, biblatexCitations
diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs
index ebde5b97c..5f702a85d 100644
--- a/tests/Tests/Writers/LaTeX.hs
+++ b/tests/Tests/Writers/LaTeX.hs
@@ -10,6 +10,9 @@ import Tests.Arbitrary()
latex :: (ToString a, ToPandoc a) => a -> String
latex = writeLaTeX def . toPandoc
+latexListing :: (ToString a, ToPandoc a) => a -> String
+latexListing = writeLaTeX def{ writerListings = True } . toPandoc
+
{-
"my test" =: X =?> Y
@@ -31,6 +34,10 @@ tests :: [Test]
tests = [ testGroup "code blocks"
[ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?>
"\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}"
+ , test latexListing "identifier" $ codeBlockWith ("id",[],[]) "hi" =?>
+ ("\\begin{lstlisting}[label=id]\nhi\n\\end{lstlisting}" :: String)
+ , test latexListing "no identifier" $ codeBlock "hi" =?>
+ ("\\begin{lstlisting}\nhi\n\\end{lstlisting}" :: String)
]
, testGroup "math"
[ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
--
cgit v1.2.3
From deb59b62354e38df9c85ce6985e5c28dd2301ee7 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sat, 24 Aug 2013 22:27:08 -0700
Subject: Removed dependency on citeproc-hs.
Going forward we'll use pandoc-citeproc, as an external filter.
The `--bibliography`, `--csl`, and `--citation-abbreviation` fields
have been removed. Instead one must include `bibliography`, `csl`,
or `csl-abbrevs` fields in the document's YAML metadata. The filter
can then be used as follows:
pandoc --filter pandoc-citeproc
The `Text.Pandoc.Biblio` module has been removed. Henceforth,
`Text.CSL.Pandoc` from pandoc-citations can be used by library users.
The Markdown and LaTeX readers now longer format bibliographies and
citations. That must be done using `processCites` or `processCites'`
from Text.CSL.Pandoc.
All bibliography-related fields have been removed from `ReaderOptions`
and `WriterOptions`: `writerBiblioFiles`, `readerReferences`,
`readerCitationStyle`.
API change.
---
README | 105 ++++-----
data/default.csl | 458 ------------------------------------
pandoc.cabal | 7 +-
pandoc.hs | 68 +-----
src/Text/Pandoc/Biblio.hs | 216 -----------------
src/Text/Pandoc/Options.hs | 7 -
src/Text/Pandoc/Readers/LaTeX.hs | 5 +-
src/Text/Pandoc/Readers/Markdown.hs | 5 +-
src/Text/Pandoc/Writers/LaTeX.hs | 8 +-
tests/Tests/Old.hs | 14 --
10 files changed, 50 insertions(+), 843 deletions(-)
delete mode 100644 data/default.csl
delete mode 100644 src/Text/Pandoc/Biblio.hs
(limited to 'src/Text/Pandoc/Writers')
diff --git a/README b/README
index 7a2b01f49..f85e62e14 100644
--- a/README
+++ b/README
@@ -598,54 +598,6 @@ Options affecting specific writers
Citation rendering
------------------
-`--bibliography=`*FILE*
-: Specify bibliography database to be used in resolving
- citations. The database type will be determined from the
- extension of *FILE*, which may be `.mods` (MODS format),
- `.bib` (BibLaTeX format, which will normally work for BibTeX
- files as well), `.bibtex` (BibTeX format),
- `.ris` (RIS format), `.enl` (EndNote format),
- `.xml` (EndNote XML format), `.wos` (ISI format),
- `.medline` (MEDLINE format), `.copac` (Copac format),
- or `.json` (citeproc JSON). If you want to use multiple
- bibliographies, just use this option repeatedly.
-
-`--csl=`*FILE*
-: Specify [CSL] style to be used in formatting citations and
- the bibliography. If *FILE* is not found, pandoc will look
- for it in
-
- $HOME/.csl
-
- in unix,
-
- C:\Documents And Settings\USERNAME\Application Data\csl
-
- in Windows XP, and
-
- C:\Users\USERNAME\AppData\Roaming\csl
-
- in Windows 7. If the `--csl` option is not specified, pandoc
- will use a default style: either `default.csl` in the
- user data directory (see `--data-dir`), or, if that is
- not present, the Chicago author-date style.
-
-`--citation-abbreviations=`*FILE*
-: Specify a file containing abbreviations for journal titles and
- other bibliographic fields (indicated by setting `form="short"`
- in the CSL node for the field). The format is described at
- .
- Here is a short example:
-
- { "default": {
- "container-title": {
- "Lloyd's Law Reports": "Lloyd's Rep",
- "Estates Gazette": "EG",
- "Scots Law Times": "SLT"
- }
- }
- }
-
`--natbib`
: Use natbib for citations in LaTeX output.
@@ -2378,9 +2330,14 @@ Citations
**Extension: `citations`**
-Pandoc can automatically generate citations and a bibliography in a number of
-styles (using Andrea Rossato's `hs-citeproc`). In order to use this feature,
-you will need a bibliographic database in one of the following formats:
+Using an external filter, `pandoc-citeproc`, pandoc can automatically generate
+citations and a bibliography in a number of styles. Basic usage is
+
+ pandoc --filter pandoc-citeproc myinput.txt
+
+In order to use this feature, you will need to specify a bibliography file
+using the `bibliography` metadata field in a YAML metadata section.
+The bibliography may have any of these formats:
Format File extension
------------ --------------
@@ -2398,18 +2355,40 @@ you will need a bibliographic database in one of the following formats:
Note that `.bib` can generally be used with both BibTeX and BibLaTeX
files, but you can use `.bibtex` to force BibTeX.
-You will need to specify the bibliography file using the `--bibliography`
-command-line option (which may be repeated if you have several
-bibliographies).
-
-By default, pandoc will use a Chicago author-date format for citations
-and references. To use another style, you will need to use the
-`--csl` option to specify a [CSL] 1.0 style file. A primer on
-creating and modifying CSL styles can be found at
-.
-A repository of CSL styles can be found at
-.
-See also for easy browsing.
+Alternatively you can use a `references` field in the document's YAML
+metadata. This should include an array of YAML-encoded references,
+for example:
+
+ ---
+ references:
+ - id: fenner2012a
+ title: One-click science marketing
+ author:
+ - family: Fenner
+ given: Martin
+ container-title: Nature Materials
+ volume: 11
+ URL: 'http://dx.doi.org/10.1038/nmat3283'
+ DOI: 10.1038/nmat3283
+ issue: 4
+ publisher: Nature Publishing Group
+ page: 261-263
+ type: article-journal
+ issued:
+ year: 2012
+ month: 3
+ ...
+
+(The program `mods2yaml`, which comes with `pandoc-citeproc`, can help produce
+these from a MODS reference collection.)
+
+By default, `pandoc-citeproc` will use a Chicago author-date format for
+citations and references. To use another style, you will need to specify
+a [CSL] 1.0 style file in the `csl` metadata field. A primer on creating and
+modifying CSL styles can be found at
+. A repository of CSL styles
+can be found at . See also
+ for easy browsing.
Citations go inside square brackets and are separated by semicolons.
Each citation must have a key, composed of '@' + the citation
diff --git a/data/default.csl b/data/default.csl
deleted file mode 100644
index 83a70d0b5..000000000
--- a/data/default.csl
+++ /dev/null
@@ -1,458 +0,0 @@
-
-
diff --git a/pandoc.cabal b/pandoc.cabal
index ac28ad068..0ab990a17 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -99,8 +99,6 @@ Data-Files:
data/slideous/slideous.js,
-- data for dzslides writer
data/dzslides/template.html,
- -- data for citeproc
- data/default.csl,
-- sample lua custom writer
data/sample.lua
-- documentation
@@ -250,7 +248,6 @@ Library
xml >= 1.3.12 && < 1.4,
random >= 1 && < 1.1,
extensible-exceptions >= 0.1 && < 0.2,
- citeproc-hs >= 0.3.7 && < 0.4,
pandoc-types >= 1.12 && < 1.13,
aeson >= 0.6 && < 0.7,
tagsoup >= 0.12.5 && < 0.14,
@@ -323,7 +320,6 @@ Library
Text.Pandoc.UTF8,
Text.Pandoc.Templates,
Text.Pandoc.XML,
- Text.Pandoc.Biblio,
Text.Pandoc.SelfContained,
Text.Pandoc.Process
Other-Modules: Text.Pandoc.Readers.Haddock.Lex,
@@ -353,8 +349,7 @@ Executable pandoc
extensible-exceptions >= 0.1 && < 0.2,
highlighting-kate >= 0.5.5 && < 0.6,
aeson >= 0.6 && < 0.7,
- HTTP >= 4000.0.5 && < 4000.3,
- citeproc-hs >= 0.3.7 && < 0.4
+ HTTP >= 4000.0.5 && < 4000.3
Ghc-Options: -rtsopts -with-rtsopts=-K16m -Wall -fno-warn-unused-do-bind
Ghc-Prof-Options: -auto-all -caf-all -rtsopts -with-rtsopts=-K16m
if os(windows)
diff --git a/pandoc.hs b/pandoc.hs
index 8eed67544..6ad5694f1 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -35,7 +35,7 @@ import Text.Pandoc.PDF (makePDF)
import Text.Pandoc.Readers.LaTeX (handleIncludes)
import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, readDataFile,
safeRead, headerShift, normalize, err, warn )
-import Text.Pandoc.XML ( toEntities, fromEntities )
+import Text.Pandoc.XML ( toEntities )
import Text.Pandoc.SelfContained ( makeSelfContained )
import Text.Pandoc.Process (pipeProcess)
import Text.Highlighting.Kate ( languages, Style, tango, pygments,
@@ -46,20 +46,18 @@ import System.FilePath
import System.Console.GetOpt
import Data.Char ( toLower )
import Data.List ( intercalate, isPrefixOf, sort )
-import System.Directory ( getAppUserDataDirectory, doesFileExist, findExecutable )
+import System.Directory ( getAppUserDataDirectory, findExecutable )
import System.IO ( stdout, stderr )
import System.IO.Error ( isDoesNotExistError )
import qualified Control.Exception as E
import Control.Exception.Extensible ( throwIO )
import qualified Text.Pandoc.UTF8 as UTF8
-import qualified Text.CSL as CSL
import Control.Monad (when, unless, liftM)
import Data.Foldable (foldrM)
import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
import Network.URI (parseURI, isURI, URI(..))
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString as BS
-import Text.CSL.Reference (Reference(..))
import Data.Aeson (eitherDecode', encode)
copyrightMessage :: String
@@ -70,7 +68,7 @@ copyrightMessage = "\nCopyright (C) 2006-2013 John MacFarlane\n" ++
compileInfo :: String
compileInfo =
- "\nCompiled with citeproc-hs " ++ VERSION_citeproc_hs ++ ", texmath " ++
+ "\nCompiled with texmath " ++
VERSION_texmath ++ ", highlighting-kate " ++ VERSION_highlighting_kate ++
".\nSyntax highlighting is supported for the following languages:\n " ++
wrapWords 4 78
@@ -146,9 +144,6 @@ data Opt = Opt
, optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks
, optDataDir :: Maybe FilePath
, optCiteMethod :: CiteMethod -- ^ Method to output cites
- , optBibliography :: [String]
- , optCslFile :: Maybe FilePath
- , optAbbrevsFile :: Maybe FilePath
, optListings :: Bool -- ^ Use listings package for code blocks
, optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
, optSlideLevel :: Maybe Int -- ^ Header level that creates slides
@@ -203,9 +198,6 @@ defaultOpts = Opt
, optIndentedCodeClasses = []
, optDataDir = Nothing
, optCiteMethod = Citeproc
- , optBibliography = []
- , optCslFile = Nothing
- , optAbbrevsFile = Nothing
, optListings = False
, optLaTeXEngine = "pdflatex"
, optSlideLevel = Nothing
@@ -650,24 +642,6 @@ options =
"PROGRAM")
"" -- "Name of latex program to use in generating PDF"
- , Option "" ["bibliography"]
- (ReqArg
- (\arg opt -> return opt { optBibliography = (optBibliography opt) ++ [arg] })
- "FILENAME")
- ""
-
- , Option "" ["csl"]
- (ReqArg
- (\arg opt -> return opt { optCslFile = Just arg })
- "FILENAME")
- ""
-
- , Option "" ["citation-abbreviations"]
- (ReqArg
- (\arg opt -> return opt { optAbbrevsFile = Just arg })
- "FILENAME")
- ""
-
, Option "" ["natbib"]
(NoArg
(\opt -> return opt { optCiteMethod = Natbib }))
@@ -904,9 +878,6 @@ main = do
, optIdentifierPrefix = idPrefix
, optIndentedCodeClasses = codeBlockClasses
, optDataDir = mbDataDir
- , optBibliography = reffiles
- , optCslFile = mbCsl
- , optAbbrevsFile = cslabbrevs
, optCiteMethod = citeMethod
, optListings = listings
, optLaTeXEngine = latexEngine
@@ -1007,36 +978,6 @@ main = do
$ lines dztempl
return $ ("dzslides-core", dzcore) : variables'
else return variables'
-
- -- unescape reference ids, which may contain XML entities, so
- -- that we can do lookups with regular string equality
- let unescapeRefId ref = ref{ refId = fromEntities (refId ref) }
-
- refs <- mapM (\f -> E.catch (CSL.readBiblioFile f)
- (\e -> let _ = (e :: E.SomeException)
- in err 23 $ "Error reading bibliography `" ++ f ++
- "'" ++ "\n" ++ show e))
- reffiles >>=
- return . map unescapeRefId . concat
-
- mbsty <- if citeMethod == Citeproc && not (null refs)
- then do
- csl <- CSL.parseCSL =<<
- case mbCsl of
- Nothing -> readDataFileUTF8 datadir
- "default.csl"
- Just cslfile -> do
- exists <- doesFileExist cslfile
- if exists
- then UTF8.readFile cslfile
- else do
- csldir <- getAppUserDataDirectory "csl"
- readDataFileUTF8 (Just csldir)
- (replaceExtension cslfile "csl")
- abbrevs <- maybe (return []) CSL.readJsonAbbrevFile cslabbrevs
- return $ Just csl { CSL.styleAbbrevs = abbrevs }
- else return Nothing
-
let sourceURL = case sources of
[] -> Nothing
(x:_) -> case parseURI x of
@@ -1054,8 +995,6 @@ main = do
, readerColumns = columns
, readerTabStop = tabStop
, readerOldDashes = oldDashes
- , readerReferences = refs
- , readerCitationStyle = mbsty
, readerIndentedCodeClasses = codeBlockClasses
, readerApplyMacros = not laTeXOutput
, readerDefaultImageExtension = defaultImageExtension
@@ -1069,7 +1008,6 @@ main = do
writerHTMLMathMethod = mathMethod,
writerIncremental = incremental,
writerCiteMethod = citeMethod,
- writerBiblioFiles = reffiles,
writerIgnoreNotes = False,
writerNumberSections = numberSections,
writerNumberOffset = numberFrom,
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs
deleted file mode 100644
index 1c0975f11..000000000
--- a/src/Text/Pandoc/Biblio.hs
+++ /dev/null
@@ -1,216 +0,0 @@
-{-# LANGUAGE PatternGuards #-}
-{-
-Copyright (C) 2008 Andrea Rossato
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
--}
-
-{- |
- Module : Text.Pandoc.Biblio
- Copyright : Copyright (C) 2008-2010 Andrea Rossato
- License : GNU GPL, version 2 or above
-
- Maintainer : Andrea Rossato
- Stability : alpha
- Portability : portable
--}
-
-module Text.Pandoc.Biblio ( processBiblio ) where
-
-import Data.List
-import Data.Char ( isDigit, isPunctuation )
-import qualified Data.Map as M
-import Text.CSL hiding ( Cite(..), Citation(..), endWithPunct )
-import qualified Text.CSL as CSL ( Cite(..) )
-import Text.Pandoc.Definition
-import Text.Pandoc.Generic
-import Text.Pandoc.Walk
-import Text.Pandoc.Shared (stringify)
-import Text.Parsec hiding (State)
-import Control.Monad
-import Control.Monad.State
-
--- | Process a 'Pandoc' document by adding citations formatted
--- according to a CSL style, using 'citeproc' from citeproc-hs.
-processBiblio :: Maybe Style -> [Reference] -> Pandoc -> Pandoc
-processBiblio Nothing _ p = p
-processBiblio _ [] p = p
-processBiblio (Just style) r p =
- let p' = evalState (bottomUpM setHash p) 1
- grps = query getCitation p'
- result = citeproc procOpts style r (setNearNote style $
- map (map toCslCite) grps)
- cits_map = M.fromList $ zip grps (citations result)
- biblioList = map (renderPandoc' style) (bibliography result)
- Pandoc m b = bottomUp mvPunct . deNote . topDown (processCite style cits_map) $ p'
- (bs, lastb) = case reverse b of
- x@(Header _ _ _) : xs -> (reverse xs, [x])
- _ -> (b, [])
- in Pandoc m $ bs ++ [Div ("",["references"],[]) (lastb ++ biblioList)]
-
--- | Substitute 'Cite' elements with formatted citations.
-processCite :: Style -> M.Map [Citation] [FormattedOutput] -> Inline -> Inline
-processCite s cs (Cite t _) =
- case M.lookup t cs of
- Just (x:xs)
- | isTextualCitation t && not (null xs) ->
- let xs' = renderPandoc s xs
- in if styleClass s == "note"
- then Cite t (renderPandoc s [x] ++ [Note [Para xs']])
- else Cite t (renderPandoc s [x] ++ [Space | not (startWithPunct xs')] ++ xs')
- | otherwise -> if styleClass s == "note"
- then Cite t [Note [Para $ renderPandoc s (x:xs)]]
- else Cite t (renderPandoc s (x:xs))
- _ -> Strong [Str "???"] -- TODO raise error instead?
-processCite _ _ x = x
-
-isNote :: Inline -> Bool
-isNote (Note _) = True
-isNote (Cite _ [Note _]) = True
-isNote _ = False
-
-mvPunct :: [Inline] -> [Inline]
-mvPunct (Space : Space : xs) = Space : xs
-mvPunct (Space : x : ys) | isNote x, startWithPunct ys =
- Str (headInline ys) : x : tailFirstInlineStr ys
-mvPunct (Space : x : ys) | isNote x = x : ys
-mvPunct xs = xs
-
--- A replacement for citeproc-hs's endWithPunct, which wrongly treats
--- a sentence ending in '.)' as not ending with punctuation, leading
--- to an extra period.
-endWithPunct :: [Inline] -> Bool
-endWithPunct [] = True
-endWithPunct xs@(_:_) = case reverse (stringify [last xs]) of
- [] -> True
- (')':c:_) | isEndPunct c -> True
- (c:_) | isEndPunct c -> True
- | otherwise -> False
- where isEndPunct c = c `elem` ".,;:!?"
-
-deNote :: Pandoc -> Pandoc
-deNote = topDown go
- where go (Cite (c:cs) [Note xs]) =
- Cite (c:cs) [Note $ bottomUp go' $ sanitize c xs]
- go (Note xs) = Note $ bottomUp go' xs
- go x = x
- go' (Note [Para xs]:ys) =
- if startWithPunct ys && endWithPunct xs
- then initInline xs ++ ys
- else xs ++ ys
- go' xs = xs
- sanitize :: Citation -> [Block] -> [Block]
- sanitize Citation{citationPrefix = pref} [Para xs] =
- case (null pref, endWithPunct xs) of
- (True, False) -> [Para $ xs ++ [Str "."]]
- (True, True) -> [Para xs]
- (False, False) -> [Para $ toCapital $ xs ++ [Str "."]]
- (False, True) -> [Para $ toCapital xs]
- sanitize _ bs = bs
-
-isTextualCitation :: [Citation] -> Bool
-isTextualCitation (c:_) = citationMode c == AuthorInText
-isTextualCitation _ = False
-
--- | Retrieve all citations from a 'Pandoc' docuument. To be used with
--- 'query'.
-getCitation :: Inline -> [[Citation]]
-getCitation i | Cite t _ <- i = [t]
- | otherwise = []
-
-setHash :: Citation -> State Int Citation
-setHash c = do
- ident <- get
- put $ ident + 1
- return c{ citationHash = ident }
-
-toCslCite :: Citation -> CSL.Cite
-toCslCite c
- = let (l, s) = locatorWords $ citationSuffix c
- (la,lo) = parseLocator l
- s' = case (l,s) of
- -- treat a bare locator as if it begins with space
- -- so @item1 [blah] is like [@item1, blah]
- ("",(x:_))
- | not (isPunct x) -> [Space] ++ s
- _ -> s
- isPunct (Str (x:_)) = isPunctuation x
- isPunct _ = False
- citMode = case citationMode c of
- AuthorInText -> (True, False)
- SuppressAuthor -> (False,True )
- NormalCitation -> (False,False)
- in emptyCite { CSL.citeId = citationId c
- , CSL.citePrefix = PandocText $ citationPrefix c
- , CSL.citeSuffix = PandocText s'
- , CSL.citeLabel = la
- , CSL.citeLocator = lo
- , CSL.citeNoteNumber = show $ citationNoteNum c
- , CSL.authorInText = fst citMode
- , CSL.suppressAuthor = snd citMode
- , CSL.citeHash = citationHash c
- }
-
-locatorWords :: [Inline] -> (String, [Inline])
-locatorWords inp =
- case parse pLocatorWords "suffix" $ breakup inp of
- Right r -> r
- Left _ -> ("",inp)
- where breakup [] = []
- breakup (Str x : xs) = map Str (splitup x) ++ breakup xs
- breakup (x : xs) = x : breakup xs
- splitup = groupBy (\x y -> x /= '\160' && y /= '\160')
-
-pLocatorWords :: Parsec [Inline] st (String, [Inline])
-pLocatorWords = do
- l <- pLocator
- s <- getInput -- rest is suffix
- if length l > 0 && last l == ','
- then return (init l, Str "," : s)
- else return (l, s)
-
-pMatch :: (Inline -> Bool) -> Parsec [Inline] st Inline
-pMatch condition = try $ do
- t <- anyToken
- guard $ condition t
- return t
-
-pSpace :: Parsec [Inline] st Inline
-pSpace = pMatch (\t -> t == Space || t == Str "\160")
-
-pLocator :: Parsec [Inline] st String
-pLocator = try $ do
- optional $ pMatch (== Str ",")
- optional pSpace
- f <- (guardFollowingDigit >> return [Str "p"]) -- "page" the default
- <|> many1 (notFollowedBy pSpace >> anyToken)
- gs <- many1 pWordWithDigits
- return $ stringify f ++ (' ' : unwords gs)
-
-guardFollowingDigit :: Parsec [Inline] st ()
-guardFollowingDigit = do
- t <- lookAhead anyToken
- case t of
- Str (d:_) | isDigit d -> return ()
- _ -> mzero
-
-pWordWithDigits :: Parsec [Inline] st String
-pWordWithDigits = try $ do
- optional pSpace
- r <- many1 (notFollowedBy pSpace >> anyToken)
- let s = stringify r
- guard $ any isDigit s
- return s
-
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index c7c37d6b8..48e418ab2 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -48,7 +48,6 @@ import Data.Set (Set)
import qualified Data.Set as Set
import Data.Default
import Text.Pandoc.Highlighting (Style, pygments)
-import qualified Text.CSL as CSL
-- | Individually selectable syntax extensions.
data Extension =
@@ -205,8 +204,6 @@ data ReaderOptions = ReaderOptions{
, readerOldDashes :: Bool -- ^ Use pandoc <= 1.8.2.1 behavior
-- in parsing dashes; -- is em-dash;
-- - before numerial is en-dash
- , readerReferences :: [CSL.Reference] -- ^ Bibliographic references
- , readerCitationStyle :: Maybe CSL.Style -- ^ Citation style
, readerApplyMacros :: Bool -- ^ Apply macros to TeX math
, readerIndentedCodeClasses :: [String] -- ^ Default classes for
-- indented code blocks
@@ -223,8 +220,6 @@ instance Default ReaderOptions
, readerColumns = 80
, readerTabStop = 4
, readerOldDashes = False
- , readerReferences = []
- , readerCitationStyle = Nothing
, readerApplyMacros = True
, readerIndentedCodeClasses = []
, readerDefaultImageExtension = ""
@@ -289,7 +284,6 @@ data WriterOptions = WriterOptions
, writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file
, writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory
, writerCiteMethod :: CiteMethod -- ^ How to print cites
- , writerBiblioFiles :: [FilePath] -- ^ Biblio files to use for citations
, writerHtml5 :: Bool -- ^ Produce HTML5
, writerHtmlQTags :: Bool -- ^ Use @@ tags for quotes in HTML
, writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show
@@ -332,7 +326,6 @@ instance Default WriterOptions where
, writerSourceURL = Nothing
, writerUserDataDir = Nothing
, writerCiteMethod = Citeproc
- , writerBiblioFiles = []
, writerHtml5 = False
, writerHtmlQTags = False
, writerBeamer = False
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index ded57df5a..e558ed1b9 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -38,7 +38,6 @@ import Text.Pandoc.Definition
import Text.Pandoc.Walk
import Text.Pandoc.Shared
import Text.Pandoc.Options
-import Text.Pandoc.Biblio (processBiblio)
import Text.Pandoc.Parsing hiding ((<|>), many, optional, space)
import qualified Text.Pandoc.UTF8 as UTF8
import Data.Char ( chr, ord )
@@ -67,9 +66,7 @@ parseLaTeX = do
eof
st <- getState
let meta = stateMeta st
- refs <- getOption readerReferences
- mbsty <- getOption readerCitationStyle
- let (Pandoc _ bs') = processBiblio mbsty refs $ doc bs
+ let (Pandoc _ bs') = doc bs
return $ Pandoc meta bs'
type LP = Parser [Char] ParserState
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 05662d9b5..658335202 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -54,7 +54,6 @@ import Text.Pandoc.Parsing hiding (tableWith)
import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockTag,
isTextTag, isCommentTag )
-import Text.Pandoc.Biblio (processBiblio)
import Data.Monoid (mconcat, mempty)
import Control.Applicative ((<$>), (<*), (*>), (<$))
import Control.Monad
@@ -327,9 +326,7 @@ parseMarkdown = do
st <- getState
let meta = runF (stateMeta' st) st
let Pandoc _ bs = B.doc $ runF blocks st
- mbsty <- getOption readerCitationStyle
- refs <- getOption readerReferences
- return $ processBiblio mbsty refs $ Pandoc meta bs
+ return $ Pandoc meta bs
addWarning :: Maybe SourcePos -> String -> MarkdownParser ()
addWarning mbpos msg =
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ab579a326..6a781ddec 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -43,7 +43,6 @@ import Data.Char ( toLower, isPunctuation )
import Control.Applicative ((<|>))
import Control.Monad.State
import Text.Pandoc.Pretty
-import System.FilePath (dropExtension)
import Text.Pandoc.Slides
import Text.Pandoc.Highlighting (highlight, styleToLaTeX,
formatLaTeXInline, formatLaTeXBlock,
@@ -120,7 +119,6 @@ pandocToLaTeX options (Pandoc meta blocks) = do
(biblioTitle :: String) <- liftM (render colwidth) $ inlineListToLaTeX lastHeader
let main = render colwidth $ vsep body
st <- get
- let biblioFiles = intercalate "," $ map dropExtension $ writerBiblioFiles options
let context = defField "toc" (writerTableOfContents options) $
defField "toc-depth" (show (writerTOCDepth options -
if writerChapters options
@@ -152,11 +150,9 @@ pandocToLaTeX options (Pandoc meta blocks) = do
$ writerHighlightStyle options )
else id) $
(case writerCiteMethod options of
- Natbib -> defField "biblio-files" biblioFiles .
- defField "biblio-title" biblioTitle .
+ Natbib -> defField "biblio-title" biblioTitle .
defField "natbib" True
- Biblatex -> defField "biblio-files" biblioFiles .
- defField "biblio-title" biblioTitle .
+ Biblatex -> defField "biblio-title" biblioTitle .
defField "biblatex" True
_ -> id) $
metadata
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index 8609781d0..5054559a1 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -63,7 +63,6 @@ tests = [ testGroup "markdown"
"markdown-reader-more.txt" "markdown-reader-more.native"
, lhsReaderTest "markdown+lhs"
]
- , testGroup "citations" markdownCitationTests
]
, testGroup "rst"
[ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst")
@@ -190,19 +189,6 @@ fb2WriterTest title opts inputfile normfile =
ignoreBinary = unlines . filter (not . startsWith " [String] -- ^ Options to pass to pandoc
--
cgit v1.2.3
From 8b0052ba5b0578814a5aca14a0e02874a10cf947 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 1 Sep 2013 15:05:51 -0700
Subject: Mathjax in HTML slide shows: include explicit "Typeset" instruction.
This seems to be needed for some formats (e.g. slideous) and won't
hurt in others.
Closes #966.
---
src/Text/Pandoc/Writers/HTML.hs | 3 ++-
1 file changed, 2 insertions(+), 1 deletion(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 25079574e..63b466af3 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -143,7 +143,8 @@ pandocToHtml opts (Pandoc meta blocks) = do
MathJax url ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
- $ mempty
+ $ preEscapedString
+ "MathJax.Hub.Queue([\"Typeset\",MathJax.Hub]);"
JsMath (Just url) ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
--
cgit v1.2.3
From 8d43e08ce7be8673cc399b948d29386f525e9e1f Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Fri, 6 Sep 2013 22:26:18 -0700
Subject: Markdown writer: Fixed bugs in YAML header output.
---
src/Text/Pandoc/Writers/Markdown.hs | 6 +++---
tests/writer.markdown | 2 +-
2 files changed, 4 insertions(+), 4 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index d617954dd..23e730bf0 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -39,7 +39,7 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (blankline, char, space)
import Data.List ( group, isPrefixOf, find, intersperse, transpose, sortBy )
-import Data.Char ( isSpace )
+import Data.Char ( isSpace, isPunctuation )
import Data.Ord ( comparing )
import Text.Pandoc.Pretty
import Control.Monad.State
@@ -143,7 +143,7 @@ jsonToYaml (Object hashmap) =
| otherwise -> (k' <> ":") $$ x
(k', Object _, x) -> (k' <> ":") $$ nest 2 x
(_, String "", _) -> empty
- (k', _, x) -> k' <> ":" <> space <> x)
+ (k', _, x) -> k' <> ":" <> space <> hang 2 "" x)
$ sortBy (comparing fst) $ H.toList hashmap
jsonToYaml (Array vec) =
vcat $ map (\v -> hang 2 "- " (jsonToYaml v)) $ V.toList vec
@@ -151,7 +151,7 @@ jsonToYaml (String "") = empty
jsonToYaml (String s) =
case T.unpack s of
x | '\n' `elem` x -> hang 2 ("|" <> cr) $ text x
- | not (any (`elem` x) "\"'#:[]{}?-") -> text x
+ | not (any isPunctuation x) -> text x
| otherwise -> text $ "'" ++ substitute "'" "''" x ++ "'"
jsonToYaml (Bool b) = text $ show b
jsonToYaml (Number n) = text $ show n
diff --git a/tests/writer.markdown b/tests/writer.markdown
index 7d67e4e87..9cf153637 100644
--- a/tests/writer.markdown
+++ b/tests/writer.markdown
@@ -2,7 +2,7 @@
author:
- John MacFarlane
- Anonymous
-date: July 17, 2006
+date: 'July 17, 2006'
title: Pandoc Test Suite
...
--
cgit v1.2.3
From 81e2df32c92ee95771f2613b9ad30aeaf11423e5 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 8 Sep 2013 15:47:50 -0700
Subject: Made . . . for pause work in all slide show formats except slideous.
---
README | 5 ++---
changelog | 5 +----
src/Text/Pandoc/Writers/HTML.hs | 22 +++++++++++++++-------
3 files changed, 18 insertions(+), 14 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/README b/README
index 7d926216b..56ad50b3c 100644
--- a/README
+++ b/README
@@ -2680,9 +2680,8 @@ a single document.
Inserting pauses
----------------
-In reveal.js and beamer slide shows, you can add "pauses" within
-a slide by including a paragraph containing three dots, separated
-by spaces:
+You can add "pauses" within a slide by including a paragraph containing
+three dots, separated by spaces:
# Slide with a pause
diff --git a/changelog b/changelog
index b7091460f..b3e9d8b0b 100644
--- a/changelog
+++ b/changelog
@@ -413,7 +413,7 @@
as markdown citations, it is redundant to have a bibliography,
since one will be generated automatically.)
- * Added syntax for "pauses" in beamer or reaveljs slide shows.
+ * Added syntax for "pauses" in slide shows:
This gives
@@ -421,9 +421,6 @@
a pause.
- [note - no longer seems to work in recente revealjs - perhaps
- this should be reverted]
-
* Use new flexible metadata type.
+ Depend on `pandoc-types` 1.12. This changes the type of
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 63b466af3..78a3edce8 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -268,11 +268,24 @@ elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elemen
else blockToHtml opts (Header level' (id',classes,keyvals) title')
let isSec (Sec _ _ _ _ _) = True
isSec (Blk _) = False
+ let isPause (Blk x) = x == Para [Str ".",Space,Str ".",Space,Str "."]
+ isPause _ = False
+ let fragmentClass = case writerSlideVariant opts of
+ RevealJsSlides -> "fragment"
+ _ -> "incremental"
+ let inDiv xs = Blk (RawBlock (Format "html") ("")) :
+ (xs ++ [Blk (RawBlock (Format "html") "
")])
innerContents <- mapM (elementToHtml slideLevel opts)
$ if titleSlide
-- title slides have no content of their own
then filter isSec elements
- else elements
+ else if slide
+ then case splitBy isPause elements of
+ [] -> []
+ [x] -> x
+ xs -> concatMap inDiv xs
+ else elements
let inNl x = mconcat $ nl opts : intersperse (nl opts) x ++ [nl opts]
let classes' = ["titleslide" | titleSlide] ++ ["slide" | slide] ++
["section" | (slide || writerSectionDivs opts) &&
@@ -401,10 +414,6 @@ blockToHtml opts (Para [Image txt (s,'f':'i':'g':':':tit)]) = do
[nl opts, img, capt, nl opts]
else H.div ! A.class_ "figure" $ mconcat
[nl opts, img, capt, nl opts]
--- . . . indicates a pause in a slideshow
-blockToHtml opts (Para [Str ".",Space,Str ".",Space,Str "."])
- | writerSlideVariant opts == RevealJsSlides =
- blockToHtml opts (RawBlock "html" "")
blockToHtml opts (Para lst) = do
contents <- inlineListToHtml opts lst
return $ H.p contents
@@ -580,8 +589,7 @@ toListItem opts item = nl opts >> H.li item
blockListToHtml :: WriterOptions -> [Block] -> State WriterState Html
blockListToHtml opts lst =
- mapM (blockToHtml opts) lst >>=
- return . mconcat . intersperse (nl opts)
+ fmap (mconcat . intersperse (nl opts)) $ mapM (blockToHtml opts) lst
-- | Convert list of Pandoc inline elements to HTML.
inlineListToHtml :: WriterOptions -> [Inline] -> State WriterState Html
--
cgit v1.2.3
From ca6842349e23b3f60cb2665d1c20de9951bea268 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 12 Sep 2013 09:24:25 -0700
Subject: HTML writer: Ensure proper escaping in header metadata.
---
changelog | 1 +
src/Text/Pandoc/Writers/HTML.hs | 9 +++++----
2 files changed, 6 insertions(+), 4 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/changelog b/changelog
index f2742664c..a892ab0ec 100644
--- a/changelog
+++ b/changelog
@@ -405,6 +405,7 @@
+ Fixed `--no-highlight` (Alexander Kondratskiy).
+ Don't convert to lowercase in email obfuscation (#839).
+ + Ensure proper escaping in `` and `` fields.
* AsciiDoc writer:
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 78a3edce8..902c8bc53 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -39,7 +39,7 @@ import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Slides
import Text.Pandoc.Highlighting ( highlight, styleToCss,
formatHtmlInline, formatHtmlBlock )
-import Text.Pandoc.XML (fromEntities)
+import Text.Pandoc.XML (fromEntities, escapeStringForXML)
import Network.HTTP ( urlEncode )
import Numeric ( showHex )
import Data.Char ( ord, toLower )
@@ -115,8 +115,9 @@ pandocToHtml opts (Pandoc meta blocks) = do
(fmap renderHtml . blockListToHtml opts)
(fmap renderHtml . inlineListToHtml opts)
meta
- let authsMeta = map stringify $ docAuthors meta
- let dateMeta = stringify $ docDate meta
+ let stringifyHTML = escapeStringForXML . stringify
+ let authsMeta = map stringifyHTML $ docAuthors meta
+ let dateMeta = stringifyHTML $ docDate meta
let slideLevel = maybe (getSlideLevel blocks) id $ writerSlideLevel opts
let sects = hierarchicalize $
if writerSlideVariant opts == NoSlides
@@ -168,7 +169,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
maybe id (defField "toc" . renderHtml) toc $
defField "author-meta" authsMeta $
maybe id (defField "date-meta") (normalizeDate dateMeta) $
- defField "pagetitle" (stringify $ docTitle meta) $
+ defField "pagetitle" (stringifyHTML $ docTitle meta) $
defField "idprefix" (writerIdentifierPrefix opts) $
-- these should maybe be set in pandoc.hs
defField "slidy-url"
--
cgit v1.2.3
From 37471041788f079632ec369a970a184864799c3d Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 12 Sep 2013 11:23:34 -0700
Subject: Markdown writer: Print references if output is 'plain'.
---
src/Text/Pandoc/Writers/Markdown.hs | 3 ++-
1 file changed, 2 insertions(+), 1 deletion(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 23e730bf0..a36bb8e14 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -189,7 +189,8 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
-- Strip off final 'references' header if markdown citations enabled
let blocks' = case reverse blocks of
(Div (_,["references"],_) _):xs
- | isEnabled Ext_citations opts -> reverse xs
+ | not isPlain && isEnabled Ext_citations opts
+ -> reverse xs
_ -> blocks
body <- blockListToMarkdown opts blocks'
st <- get
--
cgit v1.2.3
From d27e5a6ff002d575004bdb7abaebdc9c50e02b50 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 19 Sep 2013 09:48:02 -0700
Subject: DOCX writer: Add missing settings.xml to the zip container.
Closes #990.
---
src/Text/Pandoc/Writers/Docx.hs | 4 +++-
1 file changed, 3 insertions(+), 1 deletion(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index c8673ae48..1214e7f8b 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -257,6 +257,7 @@ writeDocx opts doc@(Pandoc meta _) = do
docPropsAppEntry <- entryFromArchive "docProps/app.xml"
themeEntry <- entryFromArchive "word/theme/theme1.xml"
fontTableEntry <- entryFromArchive "word/fontTable.xml"
+ settingsEntry <- entryFromArchive "word/settings.xml"
webSettingsEntry <- entryFromArchive "word/webSettings.xml"
-- Create archive
@@ -264,7 +265,8 @@ writeDocx opts doc@(Pandoc meta _) = do
contentTypesEntry : relsEntry : contentEntry : relEntry :
footnoteRelEntry : numEntry : styleEntry : footnotesEntry :
docPropsEntry : docPropsAppEntry : themeEntry :
- fontTableEntry : webSettingsEntry : imageEntries
+ fontTableEntry : settingsEntry : webSettingsEntry :
+ imageEntries
return $ fromArchive archive
styleToOpenXml :: Style -> [Element]
--
cgit v1.2.3
From e135955b1e37b4bee72ffc6d7f4dc60e99dcecae Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 19 Sep 2013 10:08:49 -0700
Subject: LaTeX writer: Don't print biblio if --natbib or --biblatex option
used.
---
src/Text/Pandoc/Writers/LaTeX.hs | 27 +++++++++++++++++----------
1 file changed, 17 insertions(+), 10 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 37ca60ce3..8b05cfb43 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -82,10 +82,17 @@ writeLaTeX options document =
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
pandocToLaTeX options (Pandoc meta blocks) = do
+ -- Strip off final 'references' header if --natbib or --biblatex
+ let method = writerCiteMethod options
+ let blocks' = if method == Biblatex || method == Natbib
+ then case reverse blocks of
+ (Div (_,["references"],_) _):xs -> reverse xs
+ _ -> blocks
+ else blocks
-- see if there are internal links
let isInternalLink (Link _ ('#':xs,_)) = [xs]
isInternalLink _ = []
- modify $ \s -> s{ stInternalLinks = query isInternalLink blocks }
+ modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' }
let template = writerTemplate options
-- set stBook depending on documentclass
let bookClasses = ["memoir","book","report","scrreprt","scrbook"]
@@ -107,15 +114,15 @@ pandocToLaTeX options (Pandoc meta blocks) = do
(fmap (render colwidth) . blockListToLaTeX)
(fmap (render colwidth) . inlineListToLaTeX)
meta
- let (blocks', lastHeader) = if writerCiteMethod options == Citeproc then
- (blocks, [])
- else case last blocks of
- Header 1 _ il -> (init blocks, il)
- _ -> (blocks, [])
- blocks'' <- if writerBeamer options
- then toSlides blocks'
- else return blocks'
- body <- mapM (elementToLaTeX options) $ hierarchicalize blocks''
+ let (blocks'', lastHeader) = if writerCiteMethod options == Citeproc then
+ (blocks', [])
+ else case last blocks' of
+ Header 1 _ il -> (init blocks', il)
+ _ -> (blocks', [])
+ blocks''' <- if writerBeamer options
+ then toSlides blocks''
+ else return blocks''
+ body <- mapM (elementToLaTeX options) $ hierarchicalize blocks'''
(biblioTitle :: String) <- liftM (render colwidth) $ inlineListToLaTeX lastHeader
let main = render colwidth $ vsep body
st <- get
--
cgit v1.2.3
From 255037a0912c5cc819985f4224057659f7af50fa Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Thu, 19 Sep 2013 10:09:32 -0700
Subject: Markdown reader: small code improvement.
---
src/Text/Pandoc/Writers/Markdown.hs | 10 +++++-----
1 file changed, 5 insertions(+), 5 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index a36bb8e14..69ca05216 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -187,11 +187,11 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
then tableOfContents opts headerBlocks
else empty
-- Strip off final 'references' header if markdown citations enabled
- let blocks' = case reverse blocks of
- (Div (_,["references"],_) _):xs
- | not isPlain && isEnabled Ext_citations opts
- -> reverse xs
- _ -> blocks
+ let blocks' = if not isPlain && isEnabled Ext_citations opts
+ then case reverse blocks of
+ (Div (_,["references"],_) _):xs -> reverse xs
+ _ -> blocks
+ else blocks
body <- blockListToMarkdown opts blocks'
st <- get
notes' <- notesToMarkdown opts (reverse $ stNotes st)
--
cgit v1.2.3
From e149d4e138fdf42df07ff8400a4748b6f7bde150 Mon Sep 17 00:00:00 2001
From: Václav Zeman
Date: Wed, 25 Sep 2013 01:18:39 +0200
Subject: src/Text/Pandoc/Writers/OpenDocument.hs: Fix formatting of strikeout
code.
---
src/Text/Pandoc/Writers/OpenDocument.hs | 19 +++++++++++++++----
1 file changed, 15 insertions(+), 4 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 3ec5c2073..0f9044601 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -192,8 +192,15 @@ writeOpenDocument opts (Pandoc meta blocks) =
listStyles = map listStyle (stListStyles s)
automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
reverse $ styles ++ listStyles
+ fontFaceDecls = inTagsIndented "office:font-face-decls" $ vcat $
+ [selfClosingTag "style:font-face" [
+ ("style:name", "Courier New")
+ , ("style:font-family-generic", "modern")
+ , ("style:font-pitch", "fixed")
+ , ("svg:font-family", "'Courier New'")]]
context = defField "body" body
$ defField "automatic-styles" (render' automaticStyles)
+ $ defField "font-face-decls" (render' fontFaceDecls)
$ metadata
in if writerStandalone opts
then renderTemplate' (writerTemplate opts) context
@@ -373,18 +380,18 @@ inlineToOpenDocument o ils
| Subscript l <- ils = withTextStyle Sub $ inlinesToOpenDocument o l
| SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l
| Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l
- | Code _ s <- ils = preformatted s
+ | Code _ s <- ils = withTextStyle Pre $ inTextStyle $ preformatted s
| Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s)
| Cite _ l <- ils = inlinesToOpenDocument o l
| RawInline f s <- ils = if f == "opendocument" || f == "html"
- then preformatted s
+ then withTextStyle Pre $ inTextStyle $ preformatted s
else return empty
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
| Image _ (s,t) <- ils = return $ mkImg s t
| Note l <- ils = mkNote l
| otherwise = return empty
where
- preformatted = return . inSpanTags "Teletype" . handleSpaces . escapeStringForXML
+ preformatted s = handleSpaces $ escapeStringForXML s
mkLink s t = inTags False "text:a" [ ("xlink:type" , "simple")
, ("xlink:href" , s )
, ("office:name", t )
@@ -524,7 +531,8 @@ paraTableStyles t s (a:xs)
[ ("fo:text-align", x)
, ("style:justify-single-word", "false")]
-data TextStyle = Italic | Bold | Strike | Sub | Sup | SmallC deriving ( Eq,Ord )
+data TextStyle = Italic | Bold | Strike | Sub | Sup | SmallC | Pre
+ deriving ( Eq,Ord )
textStyleAttr :: TextStyle -> [(String,String)]
textStyleAttr s
@@ -538,5 +546,8 @@ textStyleAttr s
| Sub <- s = [("style:text-position" ,"sub 58%" )]
| Sup <- s = [("style:text-position" ,"super 58%" )]
| SmallC <- s = [("fo:font-variant" ,"small-caps")]
+ | Pre <- s = [("style:font-name" ,"Courier New")
+ ,("style:font-name-asian" ,"Courier New")
+ ,("style:font-name-complex" ,"Courier New")]
| otherwise = []
--
cgit v1.2.3
From d76a6e23720f4acb292d3384ee020dfb072a120c Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Tue, 24 Sep 2013 18:41:19 -0700
Subject: OpenDocument writer: don't use font-face-decls variable.
---
data/templates | 2 +-
src/Text/Pandoc/Writers/OpenDocument.hs | 7 -------
2 files changed, 1 insertion(+), 8 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/data/templates b/data/templates
index 1ccb16bb3..0bb5f9ba2 160000
--- a/data/templates
+++ b/data/templates
@@ -1 +1 @@
-Subproject commit 1ccb16bb33e8022c9511284e6718386efa3a0bbf
+Subproject commit 0bb5f9ba204ea242e361c264f019490ead1cf313
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 0f9044601..206be7133 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -192,15 +192,8 @@ writeOpenDocument opts (Pandoc meta blocks) =
listStyles = map listStyle (stListStyles s)
automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
reverse $ styles ++ listStyles
- fontFaceDecls = inTagsIndented "office:font-face-decls" $ vcat $
- [selfClosingTag "style:font-face" [
- ("style:name", "Courier New")
- , ("style:font-family-generic", "modern")
- , ("style:font-pitch", "fixed")
- , ("svg:font-family", "'Courier New'")]]
context = defField "body" body
$ defField "automatic-styles" (render' automaticStyles)
- $ defField "font-face-decls" (render' fontFaceDecls)
$ metadata
in if writerStandalone opts
then renderTemplate' (writerTemplate opts) context
--
cgit v1.2.3
From dbd4aee7305ed82c9daf33a59fd0c29d3e3461d6 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 6 Oct 2013 17:21:33 -0700
Subject: Removed code that forces MathJax to typeset.
Closes #1012. Reopens #966. A better solution for #966 will just
affect slideous, not the other slide writers.
---
src/Text/Pandoc/Writers/HTML.hs | 3 +--
1 file changed, 1 insertion(+), 2 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 902c8bc53..f6775b13a 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -144,8 +144,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
MathJax url ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
- $ preEscapedString
- "MathJax.Hub.Queue([\"Typeset\",MathJax.Hub]);"
+ $ mempty
JsMath (Just url) ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
--
cgit v1.2.3
From de10b1653e0624d91bc9b0b96d2f84c4673c6d98 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Fri, 11 Oct 2013 22:01:58 -0700
Subject: RST writer: Skip spaces after display math.
Otherwise we get indentation problems, and part of the next
paragraph may be rendered as part of the math.
---
src/Text/Pandoc/Writers/RST.hs | 10 ++++++++--
1 file changed, 8 insertions(+), 2 deletions(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 70c6b4421..dd2c3186c 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -296,8 +296,14 @@ blockListToRST blocks = mapM blockToRST blocks >>= return . vcat
-- | Convert list of Pandoc inline elements to RST.
inlineListToRST :: [Inline] -> State WriterState Doc
-inlineListToRST lst = mapM inlineToRST (insertBS lst) >>= return . hcat
- where insertBS :: [Inline] -> [Inline] -- insert '\ ' where needed
+inlineListToRST lst =
+ mapM inlineToRST (removeSpaceAfterDisplayMath $ insertBS lst) >>= return . hcat
+ where -- remove spaces after displaymath, as they screw up indentation:
+ removeSpaceAfterDisplayMath (Math DisplayMath x : zs) =
+ Math DisplayMath x : dropWhile (==Space) zs
+ removeSpaceAfterDisplayMath (x:xs) = x : removeSpaceAfterDisplayMath xs
+ removeSpaceAfterDisplayMath [] = []
+ insertBS :: [Inline] -> [Inline] -- insert '\ ' where needed
insertBS (x:y:z:zs)
| isComplex y && surroundComplex x z =
x : y : RawInline "rst" "\\ " : insertBS (z:zs)
--
cgit v1.2.3
From 2ae7f5e2a0a741fa4822448ad378280f77ab0dd5 Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 13 Oct 2013 11:31:33 -0700
Subject: HTML writer: Insert command to typeset mathjax for slideous output.
Closes #966.
---
src/Text/Pandoc/Writers/HTML.hs | 6 +++++-
1 file changed, 5 insertions(+), 1 deletion(-)
(limited to 'src/Text/Pandoc/Writers')
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index f6775b13a..cee07cff5 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -144,7 +144,11 @@ pandocToHtml opts (Pandoc meta blocks) = do
MathJax url ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
- $ mempty
+ $ case writerSlideVariant opts of
+ SlideousSlides ->
+ preEscapedString
+ "MathJax.Hub.Queue([\"Typeset\",MathJax.Hub]);"
+ _ -> mempty
JsMath (Just url) ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
--
cgit v1.2.3
From 0df7cce37da162c656aa88ecb67788109749668c Mon Sep 17 00:00:00 2001
From: John MacFarlane
Date: Sun, 13 Oct 2013 15:36:19 -0700
Subject: Treat div with class "notes" as speaker notes in slide formats.
Currently beamer goes to `\note{}`, revealjs to `