2010-12-12 20:09:14 -08:00
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
{-
|
2014-05-08 21:50:20 +02:00
|
|
|
|
Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu>
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
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
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
{- |
|
2012-07-26 22:32:53 -07:00
|
|
|
|
Module : Text.Pandoc.Writers.RST
|
2014-05-08 21:50:20 +02:00
|
|
|
|
Copyright : Copyright (C) 2006-2014 John MacFarlane
|
2012-07-26 22:32:53 -07:00
|
|
|
|
License : GNU GPL, version 2 or above
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
|
Stability : alpha
|
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
|
|
Conversion of 'Pandoc' documents to reStructuredText.
|
|
|
|
|
|
|
|
|
|
reStructuredText: <http://docutils.sourceforge.net/rst.html>
|
|
|
|
|
-}
|
2013-05-10 22:53:35 -07:00
|
|
|
|
module Text.Pandoc.Writers.RST ( writeRST ) where
|
2007-11-03 23:27:58 +00:00
|
|
|
|
import Text.Pandoc.Definition
|
2012-07-26 22:59:56 -07:00
|
|
|
|
import Text.Pandoc.Options
|
2012-07-26 22:32:53 -07:00
|
|
|
|
import Text.Pandoc.Shared
|
2013-07-01 20:47:26 -07:00
|
|
|
|
import Text.Pandoc.Writers.Shared
|
2013-05-10 22:53:35 -07:00
|
|
|
|
import Text.Pandoc.Templates (renderTemplate')
|
|
|
|
|
import Text.Pandoc.Builder (deleteMeta)
|
2014-08-03 14:44:39 +04:00
|
|
|
|
import Data.Maybe (fromMaybe)
|
|
|
|
|
import Data.List ( isPrefixOf, stripPrefix, intersperse, transpose )
|
2013-10-16 09:48:11 -07:00
|
|
|
|
import Network.URI (isURI)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
import Text.Pandoc.Pretty
|
2007-11-03 23:27:58 +00:00
|
|
|
|
import Control.Monad.State
|
2008-12-02 22:43:25 +00:00
|
|
|
|
import Control.Applicative ( (<$>) )
|
2013-08-10 17:23:51 -07:00
|
|
|
|
import Data.Char (isSpace, toLower)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2010-05-08 10:03:02 -07:00
|
|
|
|
type Refs = [([Inline], Target)]
|
|
|
|
|
|
2012-07-26 22:32:53 -07:00
|
|
|
|
data WriterState =
|
2008-01-04 18:58:50 +00:00
|
|
|
|
WriterState { stNotes :: [[Block]]
|
2010-05-08 10:03:02 -07:00
|
|
|
|
, stLinks :: Refs
|
2012-09-16 11:09:36 -07:00
|
|
|
|
, stImages :: [([Inline], (String, String, Maybe String))]
|
2009-12-31 01:14:57 +00:00
|
|
|
|
, stHasMath :: Bool
|
2008-01-04 18:58:50 +00:00
|
|
|
|
, stOptions :: WriterOptions
|
|
|
|
|
}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert Pandoc to RST.
|
|
|
|
|
writeRST :: WriterOptions -> Pandoc -> String
|
2012-07-26 22:32:53 -07:00
|
|
|
|
writeRST opts document =
|
2008-01-04 18:58:50 +00:00
|
|
|
|
let st = WriterState { stNotes = [], stLinks = [],
|
2009-12-31 01:14:57 +00:00
|
|
|
|
stImages = [], stHasMath = False,
|
2008-01-04 18:58:50 +00:00
|
|
|
|
stOptions = opts }
|
2009-12-31 01:14:57 +00:00
|
|
|
|
in evalState (pandocToRST document) st
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Return RST representation of document.
|
2009-12-31 01:14:57 +00:00
|
|
|
|
pandocToRST :: Pandoc -> State WriterState String
|
2013-05-10 22:53:35 -07:00
|
|
|
|
pandocToRST (Pandoc meta blocks) = do
|
2009-12-31 01:14:57 +00:00
|
|
|
|
opts <- liftM stOptions get
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let colwidth = if writerWrapText opts
|
|
|
|
|
then Just $ writerColumns opts
|
|
|
|
|
else Nothing
|
|
|
|
|
let subtit = case lookupMeta "subtitle" meta of
|
|
|
|
|
Just (MetaBlocks [Plain xs]) -> xs
|
|
|
|
|
_ -> []
|
|
|
|
|
title <- titleToRST (docTitle meta) subtit
|
2013-07-01 20:47:26 -07:00
|
|
|
|
metadata <- metaToJSON opts
|
|
|
|
|
(fmap (render colwidth) . blockListToRST)
|
|
|
|
|
(fmap (trimr . render colwidth) . inlineListToRST)
|
|
|
|
|
$ deleteMeta "title" $ deleteMeta "subtitle" meta
|
2009-12-31 01:14:57 +00:00
|
|
|
|
body <- blockListToRST blocks
|
|
|
|
|
notes <- liftM (reverse . stNotes) get >>= notesToRST
|
|
|
|
|
-- note that the notes may contain refs, so we do them first
|
2010-05-08 10:03:02 -07:00
|
|
|
|
refs <- liftM (reverse . stLinks) get >>= refsToRST
|
|
|
|
|
pics <- liftM (reverse . stImages) get >>= pictRefsToRST
|
2009-12-31 01:14:57 +00:00
|
|
|
|
hasMath <- liftM stHasMath get
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let main = render colwidth $ foldl ($+$) empty $ [body, notes, refs, pics]
|
2013-06-27 22:42:55 -07:00
|
|
|
|
let context = defField "body" main
|
|
|
|
|
$ defField "toc" (writerTableOfContents opts)
|
|
|
|
|
$ defField "toc-depth" (writerTOCDepth opts)
|
|
|
|
|
$ defField "math" hasMath
|
|
|
|
|
$ defField "title" (render Nothing title :: String)
|
|
|
|
|
$ defField "math" hasMath
|
2013-06-29 22:14:01 -07:00
|
|
|
|
$ metadata
|
2009-12-31 01:14:57 +00:00
|
|
|
|
if writerStandalone opts
|
2013-05-10 22:53:35 -07:00
|
|
|
|
then return $ renderTemplate' (writerTemplate opts) context
|
2009-12-31 01:14:57 +00:00
|
|
|
|
else return main
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Return RST representation of reference key table.
|
2010-05-08 10:03:02 -07:00
|
|
|
|
refsToRST :: Refs -> State WriterState Doc
|
|
|
|
|
refsToRST refs = mapM keyToRST refs >>= return . vcat
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
2012-07-26 22:32:53 -07:00
|
|
|
|
-- | Return RST representation of a reference key.
|
|
|
|
|
keyToRST :: ([Inline], (String, String))
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-> State WriterState Doc
|
2008-07-13 23:16:44 +00:00
|
|
|
|
keyToRST (label, (src, _)) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
label' <- inlineListToRST label
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let label'' = if ':' `elem` (render Nothing label')
|
2007-11-03 23:27:58 +00:00
|
|
|
|
then char '`' <> label' <> char '`'
|
|
|
|
|
else label'
|
2012-04-21 09:46:05 -07:00
|
|
|
|
return $ nowrap $ ".. _" <> label'' <> ": " <> text src
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Return RST representation of notes.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
notesToRST :: [[Block]] -> State WriterState Doc
|
2012-07-26 22:32:53 -07:00
|
|
|
|
notesToRST notes =
|
2010-12-12 20:09:14 -08:00
|
|
|
|
mapM (\(num, note) -> noteToRST num note) (zip [1..] notes) >>=
|
|
|
|
|
return . vsep
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Return RST representation of a note.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
noteToRST :: Int -> [Block] -> State WriterState Doc
|
|
|
|
|
noteToRST num note = do
|
|
|
|
|
contents <- blockListToRST note
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let marker = ".. [" <> text (show num) <> "]"
|
2012-09-16 11:09:36 -07:00
|
|
|
|
return $ nowrap $ marker $$ nest 3 contents
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Return RST representation of picture reference table.
|
2012-09-16 11:09:36 -07:00
|
|
|
|
pictRefsToRST :: [([Inline], (String, String, Maybe String))]
|
|
|
|
|
-> State WriterState Doc
|
2010-05-08 10:03:02 -07:00
|
|
|
|
pictRefsToRST refs = mapM pictToRST refs >>= return . vcat
|
2010-12-12 20:09:14 -08:00
|
|
|
|
|
2012-07-26 22:32:53 -07:00
|
|
|
|
-- | Return RST representation of a picture substitution reference.
|
2012-09-16 11:09:36 -07:00
|
|
|
|
pictToRST :: ([Inline], (String, String,Maybe String))
|
2008-01-04 18:58:50 +00:00
|
|
|
|
-> State WriterState Doc
|
2012-09-16 11:09:36 -07:00
|
|
|
|
pictToRST (label, (src, _, mbtarget)) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
label' <- inlineListToRST label
|
2012-09-16 11:09:36 -07:00
|
|
|
|
return $ nowrap
|
|
|
|
|
$ ".. |" <> label' <> "| image:: " <> text src
|
|
|
|
|
$$ case mbtarget of
|
|
|
|
|
Nothing -> empty
|
|
|
|
|
Just t -> " :target: " <> text t
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Escape special characters for RST.
|
|
|
|
|
escapeString :: String -> String
|
|
|
|
|
escapeString = escapeStringUsing (backslashEscapes "`\\|*_")
|
|
|
|
|
|
2013-05-10 22:53:35 -07:00
|
|
|
|
titleToRST :: [Inline] -> [Inline] -> State WriterState Doc
|
|
|
|
|
titleToRST [] _ = return empty
|
|
|
|
|
titleToRST tit subtit = do
|
|
|
|
|
title <- inlineListToRST tit
|
|
|
|
|
subtitle <- inlineListToRST subtit
|
|
|
|
|
return $ bordered title '=' $$ bordered subtitle '-'
|
|
|
|
|
|
|
|
|
|
bordered :: Doc -> Char -> Doc
|
|
|
|
|
bordered contents c =
|
|
|
|
|
if len > 0
|
|
|
|
|
then border $$ contents $$ border
|
|
|
|
|
else empty
|
|
|
|
|
where len = offset contents
|
|
|
|
|
border = text (replicate len c)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2012-07-26 22:32:53 -07:00
|
|
|
|
-- | Convert Pandoc block element to RST.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
blockToRST :: Block -- ^ Block element
|
2012-07-26 22:32:53 -07:00
|
|
|
|
-> State WriterState Doc
|
2008-01-04 18:58:50 +00:00
|
|
|
|
blockToRST Null = return empty
|
2013-08-18 14:36:40 -07:00
|
|
|
|
blockToRST (Div attr bs) = do
|
|
|
|
|
contents <- blockListToRST bs
|
|
|
|
|
let startTag = ".. raw:: html" $+$ nest 3 (tagWithAttrs "div" attr)
|
|
|
|
|
let endTag = ".. raw:: html" $+$ nest 3 "</div>"
|
|
|
|
|
return $ blankline <> startTag $+$ contents $+$ endTag $$ blankline
|
2010-12-12 20:09:14 -08:00
|
|
|
|
blockToRST (Plain inlines) = inlineListToRST inlines
|
2013-01-15 08:45:46 -08:00
|
|
|
|
-- title beginning with fig: indicates that the image is a figure
|
|
|
|
|
blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
|
2010-03-18 02:38:58 +00:00
|
|
|
|
capt <- inlineListToRST txt
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let fig = "figure:: " <> text src
|
|
|
|
|
let alt = ":alt: " <> if null tit then capt else text tit
|
2012-11-04 18:33:35 -08:00
|
|
|
|
return $ hang 3 ".. " $ fig $$ alt $+$ capt $$ blankline
|
2013-01-13 09:25:56 -08:00
|
|
|
|
blockToRST (Para inlines)
|
2014-07-12 22:57:22 -07:00
|
|
|
|
| LineBreak `elem` inlines = do -- use line block if LineBreaks
|
2013-01-13 09:25:56 -08:00
|
|
|
|
lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines
|
2013-01-13 11:15:51 -08:00
|
|
|
|
return $ (vcat $ map (text "| " <>) lns) <> blankline
|
2013-01-13 09:25:56 -08:00
|
|
|
|
| otherwise = do
|
|
|
|
|
contents <- inlineListToRST inlines
|
|
|
|
|
return $ contents <> blankline
|
2013-08-14 23:24:45 -07:00
|
|
|
|
blockToRST (RawBlock f@(Format f') str)
|
2013-08-10 17:23:51 -07:00
|
|
|
|
| f == "rst" = return $ text str
|
|
|
|
|
| otherwise = return $ blankline <> ".. raw:: " <>
|
2013-08-14 23:24:45 -07:00
|
|
|
|
text (map toLower f') $+$
|
2013-08-10 17:23:51 -07:00
|
|
|
|
(nest 3 $ text str) $$ blankline
|
2010-12-12 20:09:14 -08:00
|
|
|
|
blockToRST HorizontalRule =
|
|
|
|
|
return $ blankline $$ "--------------" $$ blankline
|
2012-10-29 22:45:52 -07:00
|
|
|
|
blockToRST (Header level _ inlines) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
contents <- inlineListToRST inlines
|
2007-11-03 23:27:58 +00:00
|
|
|
|
let headerChar = if level > 5 then ' ' else "=-~^'" !! (level - 1)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let border = text $ replicate (offset contents) headerChar
|
2012-02-08 08:40:53 -08:00
|
|
|
|
return $ nowrap $ contents $$ border $$ blankline
|
2013-03-06 10:13:12 -08:00
|
|
|
|
blockToRST (CodeBlock (_,classes,kvs) str) = do
|
2008-12-02 22:43:25 +00:00
|
|
|
|
opts <- stOptions <$> get
|
|
|
|
|
let tabstop = writerTabStop opts
|
2013-03-06 10:13:12 -08:00
|
|
|
|
let startnum = maybe "" (\x -> " " <> text x) $ lookup "startFrom" kvs
|
|
|
|
|
let numberlines = if "numberLines" `elem` classes
|
|
|
|
|
then " :number-lines:" <> startnum
|
|
|
|
|
else empty
|
2009-11-03 06:50:17 +00:00
|
|
|
|
if "haskell" `elem` classes && "literate" `elem` classes &&
|
2012-08-08 23:18:19 -07:00
|
|
|
|
isEnabled Ext_literate_haskell opts
|
2011-01-06 21:03:08 -08:00
|
|
|
|
then return $ prefixed "> " (text str) $$ blankline
|
2013-01-26 16:09:41 -08:00
|
|
|
|
else return $
|
|
|
|
|
(case [c | c <- classes,
|
|
|
|
|
c `notElem` ["sourceCode","literate","numberLines"]] of
|
|
|
|
|
[] -> "::"
|
2013-03-06 10:13:12 -08:00
|
|
|
|
(lang:_) -> (".. code:: " <> text lang) $$ numberlines)
|
2013-01-26 16:09:41 -08:00
|
|
|
|
$+$ nest tabstop (text str) $$ blankline
|
2008-01-04 18:58:50 +00:00
|
|
|
|
blockToRST (BlockQuote blocks) = do
|
|
|
|
|
tabstop <- get >>= (return . writerTabStop . stOptions)
|
2012-07-26 22:32:53 -07:00
|
|
|
|
contents <- blockListToRST blocks
|
2011-01-06 21:03:08 -08:00
|
|
|
|
return $ (nest tabstop contents) <> blankline
|
2008-07-13 23:16:44 +00:00
|
|
|
|
blockToRST (Table caption _ widths headers rows) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
caption' <- inlineListToRST caption
|
2007-11-03 23:27:58 +00:00
|
|
|
|
let caption'' = if null caption
|
|
|
|
|
then empty
|
2010-12-12 20:09:14 -08:00
|
|
|
|
else blankline <> text "Table: " <> caption'
|
2008-01-04 18:58:50 +00:00
|
|
|
|
headers' <- mapM blockListToRST headers
|
2009-11-28 03:22:33 +00:00
|
|
|
|
rawRows <- mapM (mapM blockListToRST) rows
|
2014-03-14 14:03:15 -07:00
|
|
|
|
-- let isSimpleCell [Plain _] = True
|
|
|
|
|
-- isSimpleCell [Para _] = True
|
|
|
|
|
-- isSimpleCell [] = True
|
|
|
|
|
-- isSimpleCell _ = False
|
|
|
|
|
-- let isSimple = all (==0) widths && all (all isSimpleCell) rows
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let numChars = maximum . map offset
|
|
|
|
|
opts <- get >>= return . stOptions
|
2009-11-28 03:22:33 +00:00
|
|
|
|
let widthsInChars =
|
2014-03-14 14:03:15 -07:00
|
|
|
|
if all (== 0) widths
|
2009-11-28 03:22:33 +00:00
|
|
|
|
then map ((+2) . numChars) $ transpose (headers' : rawRows)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
else map (floor . (fromIntegral (writerColumns opts) *)) widths
|
2012-07-26 22:32:53 -07:00
|
|
|
|
let hpipeBlocks blocks = hcat [beg, middle, end]
|
2010-12-12 20:09:14 -08:00
|
|
|
|
where h = maximum (map height blocks)
|
|
|
|
|
sep' = lblock 3 $ vcat (map text $ replicate h " | ")
|
|
|
|
|
beg = lblock 2 $ vcat (map text $ replicate h "| ")
|
|
|
|
|
end = lblock 2 $ vcat (map text $ replicate h " |")
|
|
|
|
|
middle = hcat $ intersperse sep' blocks
|
|
|
|
|
let makeRow = hpipeBlocks . zipWith lblock widthsInChars
|
2008-07-13 23:16:44 +00:00
|
|
|
|
let head' = makeRow headers'
|
2008-01-04 18:58:50 +00:00
|
|
|
|
rows' <- mapM (\row -> do cols <- mapM blockListToRST row
|
2007-11-03 23:27:58 +00:00
|
|
|
|
return $ makeRow cols) rows
|
|
|
|
|
let border ch = char '+' <> char ch <>
|
2012-07-26 22:32:53 -07:00
|
|
|
|
(hcat $ intersperse (char ch <> char '+' <> char ch) $
|
2007-11-03 23:27:58 +00:00
|
|
|
|
map (\l -> text $ replicate l ch) widthsInChars) <>
|
|
|
|
|
char ch <> char '+'
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let body = vcat $ intersperse (border '-') rows'
|
2010-03-11 03:01:27 +00:00
|
|
|
|
let head'' = if all null headers
|
|
|
|
|
then empty
|
2010-12-12 20:09:14 -08:00
|
|
|
|
else head' $$ border '='
|
|
|
|
|
return $ border '-' $$ head'' $$ body $$ border '-' $$ caption'' $$ blankline
|
2008-01-04 18:58:50 +00:00
|
|
|
|
blockToRST (BulletList items) = do
|
|
|
|
|
contents <- mapM bulletListItemToRST items
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- ensure that sublists have preceding blank line
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ blankline $$ vcat contents $$ blankline
|
2008-07-13 23:16:44 +00:00
|
|
|
|
blockToRST (OrderedList (start, style', delim) items) = do
|
2012-07-26 22:32:53 -07:00
|
|
|
|
let markers = if start == 1 && style' == DefaultStyle && delim == DefaultDelim
|
2007-11-03 23:27:58 +00:00
|
|
|
|
then take (length items) $ repeat "#."
|
2012-07-26 22:32:53 -07:00
|
|
|
|
else take (length items) $ orderedListMarkers
|
2008-07-13 23:16:44 +00:00
|
|
|
|
(start, style', delim)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
let maxMarkerLength = maximum $ map length markers
|
|
|
|
|
let markers' = map (\m -> let s = maxMarkerLength - length m
|
|
|
|
|
in m ++ replicate s ' ') markers
|
2008-01-04 18:58:50 +00:00
|
|
|
|
contents <- mapM (\(item, num) -> orderedListItemToRST item num) $
|
2010-12-12 20:09:14 -08:00
|
|
|
|
zip markers' items
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- ensure that sublists have preceding blank line
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ blankline $$ vcat contents $$ blankline
|
2008-01-04 18:58:50 +00:00
|
|
|
|
blockToRST (DefinitionList items) = do
|
|
|
|
|
contents <- mapM definitionListItemToRST items
|
2010-12-12 20:09:14 -08:00
|
|
|
|
-- ensure that sublists have preceding blank line
|
|
|
|
|
return $ blankline $$ vcat contents $$ blankline
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert bullet list item (list of blocks) to RST.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
bulletListItemToRST :: [Block] -> State WriterState Doc
|
|
|
|
|
bulletListItemToRST items = do
|
|
|
|
|
contents <- blockListToRST items
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ hang 3 "- " $ contents <> cr
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert ordered list item (a list of blocks) to RST.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
orderedListItemToRST :: String -- ^ marker for list item
|
|
|
|
|
-> [Block] -- ^ list item (list of blocks)
|
|
|
|
|
-> State WriterState Doc
|
|
|
|
|
orderedListItemToRST marker items = do
|
|
|
|
|
contents <- blockListToRST items
|
2010-12-12 20:09:14 -08:00
|
|
|
|
let marker' = marker ++ " "
|
|
|
|
|
return $ hang (length marker') (text marker') $ contents <> cr
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert defintion list item (label, list of blocks) to RST.
|
2009-12-07 08:26:53 +00:00
|
|
|
|
definitionListItemToRST :: ([Inline], [[Block]]) -> State WriterState Doc
|
|
|
|
|
definitionListItemToRST (label, defs) = do
|
2008-07-13 23:16:44 +00:00
|
|
|
|
label' <- inlineListToRST label
|
2009-12-07 08:26:53 +00:00
|
|
|
|
contents <- liftM vcat $ mapM blockListToRST defs
|
2008-01-04 18:58:50 +00:00
|
|
|
|
tabstop <- get >>= (return . writerTabStop . stOptions)
|
2014-01-02 21:10:14 -08:00
|
|
|
|
return $ label' $$ nest tabstop (nestle contents <> cr)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert list of Pandoc block elements to RST.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
blockListToRST :: [Block] -- ^ List of block elements
|
2012-07-26 22:32:53 -07:00
|
|
|
|
-> State WriterState Doc
|
2008-01-04 18:58:50 +00:00
|
|
|
|
blockListToRST blocks = mapM blockToRST blocks >>= return . vcat
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert list of Pandoc inline elements to RST.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
inlineListToRST :: [Inline] -> State WriterState Doc
|
2013-10-11 22:01:58 -07:00
|
|
|
|
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
|
2012-03-24 15:53:57 -07:00
|
|
|
|
insertBS (x:y:z:zs)
|
|
|
|
|
| isComplex y && surroundComplex x z =
|
|
|
|
|
x : y : RawInline "rst" "\\ " : insertBS (z:zs)
|
|
|
|
|
insertBS (x:y:zs)
|
|
|
|
|
| isComplex x && not (okAfterComplex y) =
|
|
|
|
|
x : RawInline "rst" "\\ " : insertBS (y : zs)
|
|
|
|
|
| isComplex y && not (okBeforeComplex x) =
|
|
|
|
|
x : RawInline "rst" "\\ " : insertBS (y : zs)
|
|
|
|
|
| otherwise =
|
|
|
|
|
x : insertBS (y : zs)
|
|
|
|
|
insertBS (x:ys) = x : insertBS ys
|
|
|
|
|
insertBS [] = []
|
|
|
|
|
surroundComplex :: Inline -> Inline -> Bool
|
|
|
|
|
surroundComplex (Str s@(_:_)) (Str s'@(_:_)) =
|
|
|
|
|
case (last s, head s') of
|
|
|
|
|
('\'','\'') -> True
|
|
|
|
|
('"','"') -> True
|
|
|
|
|
('<','>') -> True
|
|
|
|
|
('[',']') -> True
|
|
|
|
|
('{','}') -> True
|
|
|
|
|
_ -> False
|
|
|
|
|
surroundComplex _ _ = False
|
|
|
|
|
okAfterComplex :: Inline -> Bool
|
|
|
|
|
okAfterComplex Space = True
|
|
|
|
|
okAfterComplex LineBreak = True
|
|
|
|
|
okAfterComplex (Str (c:_)) = isSpace c || c `elem` "-.,:;!?\\/'\")]}>–—"
|
|
|
|
|
okAfterComplex _ = False
|
|
|
|
|
okBeforeComplex :: Inline -> Bool
|
|
|
|
|
okBeforeComplex Space = True
|
|
|
|
|
okBeforeComplex LineBreak = True
|
|
|
|
|
okBeforeComplex (Str (c:_)) = isSpace c || c `elem` "-:/'\"<([{–—"
|
|
|
|
|
okBeforeComplex _ = False
|
|
|
|
|
isComplex :: Inline -> Bool
|
|
|
|
|
isComplex (Emph _) = True
|
|
|
|
|
isComplex (Strong _) = True
|
|
|
|
|
isComplex (SmallCaps _) = True
|
|
|
|
|
isComplex (Strikeout _) = True
|
|
|
|
|
isComplex (Superscript _) = True
|
|
|
|
|
isComplex (Subscript _) = True
|
|
|
|
|
isComplex (Link _ _) = True
|
|
|
|
|
isComplex (Image _ _) = True
|
|
|
|
|
isComplex (Code _ _) = True
|
|
|
|
|
isComplex (Math _ _) = True
|
|
|
|
|
isComplex _ = False
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Convert Pandoc inline element to RST.
|
2008-01-04 18:58:50 +00:00
|
|
|
|
inlineToRST :: Inline -> State WriterState Doc
|
2013-08-08 23:14:12 -07:00
|
|
|
|
inlineToRST (Span _ ils) = inlineListToRST ils
|
2012-07-26 22:32:53 -07:00
|
|
|
|
inlineToRST (Emph lst) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
contents <- inlineListToRST lst
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ "*" <> contents <> "*"
|
2008-01-04 18:58:50 +00:00
|
|
|
|
inlineToRST (Strong lst) = do
|
|
|
|
|
contents <- inlineListToRST lst
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ "**" <> contents <> "**"
|
2012-07-26 22:32:53 -07:00
|
|
|
|
inlineToRST (Strikeout lst) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
contents <- inlineListToRST lst
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ "[STRIKEOUT:" <> contents <> "]"
|
2012-07-26 22:32:53 -07:00
|
|
|
|
inlineToRST (Superscript lst) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
contents <- inlineListToRST lst
|
2012-03-24 15:53:57 -07:00
|
|
|
|
return $ ":sup:`" <> contents <> "`"
|
2012-07-26 22:32:53 -07:00
|
|
|
|
inlineToRST (Subscript lst) = do
|
2008-01-04 18:58:50 +00:00
|
|
|
|
contents <- inlineListToRST lst
|
2012-03-24 15:53:57 -07:00
|
|
|
|
return $ ":sub:`" <> contents <> "`"
|
2008-07-15 23:26:06 +00:00
|
|
|
|
inlineToRST (SmallCaps lst) = inlineListToRST lst
|
2008-01-04 18:58:50 +00:00
|
|
|
|
inlineToRST (Quoted SingleQuote lst) = do
|
|
|
|
|
contents <- inlineListToRST lst
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ "‘" <> contents <> "’"
|
2008-01-04 18:58:50 +00:00
|
|
|
|
inlineToRST (Quoted DoubleQuote lst) = do
|
|
|
|
|
contents <- inlineListToRST lst
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ "“" <> contents <> "”"
|
2008-08-04 03:15:12 +00:00
|
|
|
|
inlineToRST (Cite _ lst) =
|
|
|
|
|
inlineListToRST lst
|
2011-01-26 20:44:25 -08:00
|
|
|
|
inlineToRST (Code _ str) = return $ "``" <> text str <> "``"
|
2008-01-04 18:58:50 +00:00
|
|
|
|
inlineToRST (Str str) = return $ text $ escapeString str
|
2008-08-13 03:02:42 +00:00
|
|
|
|
inlineToRST (Math t str) = do
|
2009-12-31 01:14:57 +00:00
|
|
|
|
modify $ \st -> st{ stHasMath = True }
|
2008-08-13 03:02:42 +00:00
|
|
|
|
return $ if t == InlineMath
|
2012-03-24 15:53:57 -07:00
|
|
|
|
then ":math:`" <> text str <> "`"
|
2011-12-31 11:40:47 -08:00
|
|
|
|
else if '\n' `elem` str
|
|
|
|
|
then blankline $$ ".. math::" $$
|
|
|
|
|
blankline $$ nest 3 (text str) $$ blankline
|
|
|
|
|
else blankline $$ (".. math:: " <> text str) $$ blankline
|
2013-08-10 17:23:51 -07:00
|
|
|
|
inlineToRST (RawInline f x)
|
|
|
|
|
| f == "rst" = return $ text x
|
|
|
|
|
| otherwise = return empty
|
2013-01-13 09:25:56 -08:00
|
|
|
|
inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para)
|
2010-12-12 20:09:14 -08:00
|
|
|
|
inlineToRST Space = return space
|
2013-01-06 20:51:51 -08:00
|
|
|
|
-- autolink
|
|
|
|
|
inlineToRST (Link [Str str] (src, _))
|
2013-10-16 09:48:11 -07:00
|
|
|
|
| isURI src &&
|
2013-04-14 22:37:46 -07:00
|
|
|
|
if "mailto:" `isPrefixOf` src
|
|
|
|
|
then src == escapeURI ("mailto:" ++ str)
|
|
|
|
|
else src == escapeURI str = do
|
2014-08-03 14:44:39 +04:00
|
|
|
|
let srcSuffix = fromMaybe src (stripPrefix "mailto:" src)
|
2011-12-02 19:39:30 -08:00
|
|
|
|
return $ text srcSuffix
|
2012-09-16 11:09:36 -07:00
|
|
|
|
inlineToRST (Link [Image alt (imgsrc,imgtit)] (src, _tit)) = do
|
|
|
|
|
label <- registerImage alt (imgsrc,imgtit) (Just src)
|
|
|
|
|
return $ "|" <> label <> "|"
|
2011-12-02 19:39:30 -08:00
|
|
|
|
inlineToRST (Link txt (src, tit)) = do
|
2010-12-12 20:09:14 -08:00
|
|
|
|
useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions
|
2008-01-04 18:58:50 +00:00
|
|
|
|
linktext <- inlineListToRST $ normalizeSpaces txt
|
2007-11-03 23:27:58 +00:00
|
|
|
|
if useReferenceLinks
|
2010-12-12 20:09:14 -08:00
|
|
|
|
then do refs <- get >>= return . stLinks
|
2013-01-13 23:00:05 -08:00
|
|
|
|
case lookup txt refs of
|
|
|
|
|
Just (src',tit') ->
|
|
|
|
|
if src == src' && tit == tit'
|
|
|
|
|
then return $ "`" <> linktext <> "`_"
|
|
|
|
|
else do -- duplicate label, use non-reference link
|
|
|
|
|
return $ "`" <> linktext <> " <" <> text src <> ">`__"
|
|
|
|
|
Nothing -> do
|
|
|
|
|
modify $ \st -> st { stLinks = (txt,(src,tit)):refs }
|
|
|
|
|
return $ "`" <> linktext <> "`_"
|
|
|
|
|
else return $ "`" <> linktext <> " <" <> text src <> ">`__"
|
2011-12-02 19:39:30 -08:00
|
|
|
|
inlineToRST (Image alternate (source, tit)) = do
|
2012-09-16 11:09:36 -07:00
|
|
|
|
label <- registerImage alternate (source,tit) Nothing
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ "|" <> label <> "|"
|
2012-07-26 22:32:53 -07:00
|
|
|
|
inlineToRST (Note contents) = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
-- add to notes in state
|
2010-12-12 20:09:14 -08:00
|
|
|
|
notes <- get >>= return . stNotes
|
2008-01-04 18:58:50 +00:00
|
|
|
|
modify $ \st -> st { stNotes = contents:notes }
|
|
|
|
|
let ref = show $ (length notes) + 1
|
2010-12-12 20:09:14 -08:00
|
|
|
|
return $ " [" <> text ref <> "]_"
|
2012-09-16 11:09:36 -07:00
|
|
|
|
|
|
|
|
|
registerImage :: [Inline] -> Target -> Maybe String -> State WriterState Doc
|
|
|
|
|
registerImage alt (src,tit) mbtarget = do
|
|
|
|
|
pics <- get >>= return . stImages
|
|
|
|
|
txt <- case lookup alt pics of
|
|
|
|
|
Just (s,t,mbt) | (s,t,mbt) == (src,tit,mbtarget) -> return alt
|
2013-01-13 20:24:34 -08:00
|
|
|
|
_ -> do
|
|
|
|
|
let alt' = if null alt || alt == [Str ""]
|
|
|
|
|
then [Str $ "image" ++ show (length pics)]
|
|
|
|
|
else alt
|
|
|
|
|
modify $ \st -> st { stImages =
|
|
|
|
|
(alt', (src,tit, mbtarget)):stImages st }
|
|
|
|
|
return alt'
|
2012-09-16 11:09:36 -07:00
|
|
|
|
inlineListToRST txt
|