pandoc/src/Text/Pandoc/Writers/Textile.hs

504 lines
19 KiB
Haskell
Raw Normal View History

2010-04-10 12:38:07 -07:00
{-
Copyright (C) 2010-2017 John MacFarlane <jgm@berkeley.edu>
2010-04-10 12:38:07 -07: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
-}
{- |
Module : Text.Pandoc.Writers.Textile
Copyright : Copyright (C) 2010-2017 John MacFarlane
2012-07-26 22:32:53 -07:00
License : GNU GPL, version 2 or above
2010-04-10 12:38:07 -07:00
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
Portability : portable
Conversion of 'Pandoc' documents to Textile markup.
Textile: <http://thresholdstate.com/articles/4312/the-textile-reference-manual>
-}
module Text.Pandoc.Writers.Textile ( writeTextile ) where
import Control.Monad.State
import Data.Char (isSpace)
import Data.List (intercalate)
import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Logging
2010-04-10 12:38:07 -07:00
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
import Text.Pandoc.Options
import Text.Pandoc.Pretty (render)
import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Writers.Shared
import Text.Pandoc.XML (escapeStringForXML)
2010-04-10 12:38:07 -07:00
data WriterState = WriterState {
stNotes :: [String] -- Footnotes
, stListLevel :: [Char] -- String at beginning of list items, e.g. "**"
, stStartNum :: Maybe Int -- Start number if first list item
2010-04-10 12:38:07 -07:00
, stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list
}
type TW = StateT WriterState
2010-04-10 12:38:07 -07:00
-- | Convert Pandoc to Textile.
writeTextile :: PandocMonad m => WriterOptions -> Pandoc -> m String
writeTextile opts document =
evalStateT (pandocToTextile opts document)
WriterState { stNotes = [],
stListLevel = [],
stStartNum = Nothing,
stUseTags = False }
2010-04-10 12:38:07 -07:00
-- | Return Textile representation of document.
pandocToTextile :: PandocMonad m
=> WriterOptions -> Pandoc -> TW m String
pandocToTextile opts (Pandoc meta blocks) = do
metadata <- metaToJSON opts (blockListToTextile opts)
(inlineListToTextile opts) meta
2010-04-10 12:38:07 -07:00
body <- blockListToTextile opts blocks
notes <- gets $ unlines . reverse . stNotes
2010-04-10 12:38:07 -07:00
let main = body ++ if null notes then "" else ("\n\n" ++ notes)
let context = defField "body" main metadata
case writerTemplate opts of
Nothing -> return main
Just tpl -> return $ renderTemplate' tpl context
2010-04-10 12:38:07 -07:00
withUseTags :: PandocMonad m => TW m a -> TW m a
2010-04-10 12:38:07 -07:00
withUseTags action = do
oldUseTags <- gets stUseTags
2010-04-10 12:38:07 -07:00
modify $ \s -> s { stUseTags = True }
result <- action
modify $ \s -> s { stUseTags = oldUseTags }
return result
-- | Escape one character as needed for Textile.
escapeCharForTextile :: Char -> String
escapeCharForTextile x = case x of
'&' -> "&amp;"
'<' -> "&lt;"
'>' -> "&gt;"
'"' -> "&quot;"
'*' -> "&#42;"
'_' -> "&#95;"
'@' -> "&#64;"
'+' -> "&#43;"
'-' -> "&#45;"
'|' -> "&#124;"
'\x2014' -> " -- "
'\x2013' -> " - "
'\x2019' -> "'"
'\x2026' -> "..."
c -> [c]
2010-04-10 12:38:07 -07:00
-- | Escape string as needed for Textile.
escapeStringForTextile :: String -> String
escapeStringForTextile = concatMap escapeCharForTextile
2012-07-26 22:32:53 -07:00
-- | Convert Pandoc block element to Textile.
blockToTextile :: PandocMonad m
=> WriterOptions -- ^ Options
-> Block -- ^ Block element
-> TW m String
2010-04-10 12:38:07 -07:00
blockToTextile _ Null = return ""
blockToTextile opts (Div attr bs) = do
let startTag = render Nothing $ tagWithAttrs "div" attr
let endTag = "</div>"
contents <- blockListToTextile opts bs
return $ startTag ++ "\n\n" ++ contents ++ "\n\n" ++ endTag ++ "\n"
2012-07-26 22:32:53 -07:00
blockToTextile opts (Plain inlines) =
2010-04-10 12:38:07 -07:00
inlineListToTextile opts inlines
-- title beginning with fig: indicates that the image is a figure
blockToTextile opts (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
2010-04-10 12:38:07 -07:00
capt <- blockToTextile opts (Para txt)
im <- inlineToTextile opts (Image attr txt (src,tit))
2010-04-10 12:38:07 -07:00
return $ im ++ "\n" ++ capt
blockToTextile opts (Para inlines) = do
useTags <- gets stUseTags
listLevel <- gets stListLevel
2010-04-10 12:38:07 -07:00
contents <- inlineListToTextile opts inlines
return $ if useTags
then "<p>" ++ contents ++ "</p>"
2010-04-10 12:38:07 -07:00
else contents ++ if null listLevel then "\n" else ""
blockToTextile opts (LineBlock lns) =
blockToTextile opts $ linesToPara lns
blockToTextile _ b@(RawBlock f str)
2013-08-10 17:23:51 -07:00
| f == Format "html" || f == Format "textile" = return str
| otherwise = do
report $ BlockNotRendered b
return ""
2010-04-10 12:38:07 -07:00
blockToTextile _ HorizontalRule = return "<hr />\n"
blockToTextile opts (Header level (ident,classes,keyvals) inlines) = do
2010-04-10 12:38:07 -07:00
contents <- inlineListToTextile opts inlines
let identAttr = if null ident then "" else ('#':ident)
let attribs = if null identAttr && null classes
then ""
else "(" ++ unwords classes ++ identAttr ++ ")"
let lang = maybe "" (\x -> "[" ++ x ++ "]") $ lookup "lang" keyvals
let styles = maybe "" (\x -> "{" ++ x ++ "}") $ lookup "style" keyvals
let prefix = 'h' : show level ++ attribs ++ styles ++ lang ++ ". "
2010-04-10 12:38:07 -07:00
return $ prefix ++ contents ++ "\n"
blockToTextile _ (CodeBlock (_,classes,_) str) | any (all isSpace) (lines str) =
return $ "<pre" ++ classes' ++ ">\n" ++ escapeStringForXML str ++
"\n</pre>\n"
where classes' = if null classes
then ""
else " class=\"" ++ unwords classes ++ "\""
2010-04-10 12:38:07 -07:00
blockToTextile _ (CodeBlock (_,classes,_) str) =
return $ "bc" ++ classes' ++ ". " ++ str ++ "\n\n"
2010-04-10 12:38:07 -07:00
where classes' = if null classes
then ""
else "(" ++ unwords classes ++ ")"
blockToTextile opts (BlockQuote bs@[Para _]) = do
contents <- blockListToTextile opts bs
return $ "bq. " ++ contents ++ "\n\n"
2010-04-10 12:38:07 -07:00
blockToTextile opts (BlockQuote blocks) = do
contents <- blockListToTextile opts blocks
return $ "<blockquote>\n\n" ++ contents ++ "\n</blockquote>\n"
blockToTextile opts (Table [] aligns widths headers rows') |
all (==0) widths = do
2010-04-10 12:38:07 -07:00
hs <- mapM (liftM (("_. " ++) . stripTrailingNewlines) . blockListToTextile opts) headers
let cellsToRow cells = "|" ++ intercalate "|" cells ++ "|"
let header = if all null headers then "" else cellsToRow hs ++ "\n"
let blocksToCell (align, bs) = do
contents <- stripTrailingNewlines <$> blockListToTextile opts bs
let alignMarker = case align of
AlignLeft -> "<. "
AlignRight -> ">. "
AlignCenter -> "=. "
AlignDefault -> ""
return $ alignMarker ++ contents
let rowToCells = mapM blocksToCell . zip aligns
2010-04-10 12:38:07 -07:00
bs <- mapM rowToCells rows'
let body = unlines $ map cellsToRow bs
return $ header ++ body
2010-04-10 12:38:07 -07:00
blockToTextile opts (Table capt aligns widths headers rows') = do
let alignStrings = map alignmentToString aligns
captionDoc <- if null capt
then return ""
else do
c <- inlineListToTextile opts capt
return $ "<caption>" ++ c ++ "</caption>\n"
2010-04-10 12:38:07 -07:00
let percent w = show (truncate (100*w) :: Integer) ++ "%"
let coltags = if all (== 0.0) widths
then ""
else unlines $ map
(\w -> "<col width=\"" ++ percent w ++ "\" />") widths
2010-04-10 12:38:07 -07:00
head' <- if all null headers
then return ""
else do
hs <- tableRowToTextile opts alignStrings 0 headers
return $ "<thead>\n" ++ hs ++ "\n</thead>\n"
2010-04-10 12:38:07 -07:00
body' <- zipWithM (tableRowToTextile opts alignStrings) [1..] rows'
return $ "<table>\n" ++ captionDoc ++ coltags ++ head' ++
"<tbody>\n" ++ unlines body' ++ "</tbody>\n</table>\n"
2010-04-10 12:38:07 -07:00
blockToTextile opts x@(BulletList items) = do
oldUseTags <- gets stUseTags
2010-04-10 12:38:07 -07:00
let useTags = oldUseTags || not (isSimpleList x)
if useTags
then do
contents <- withUseTags $ mapM (listItemToTextile opts) items
return $ "<ul>\n" ++ vcat contents ++ "\n</ul>\n"
2010-04-10 12:38:07 -07:00
else do
modify $ \s -> s { stListLevel = stListLevel s ++ "*" }
level <- gets $ length . stListLevel
2010-04-10 12:38:07 -07:00
contents <- mapM (listItemToTextile opts) items
modify $ \s -> s { stListLevel = init (stListLevel s) }
return $ vcat contents ++ (if level > 1 then "" else "\n")
2010-04-10 12:38:07 -07:00
blockToTextile opts x@(OrderedList attribs@(start, _, _) items) = do
oldUseTags <- gets stUseTags
2010-04-10 12:38:07 -07:00
let useTags = oldUseTags || not (isSimpleList x)
if useTags
then do
contents <- withUseTags $ mapM (listItemToTextile opts) items
return $ "<ol" ++ listAttribsToString attribs ++ ">\n" ++ vcat contents ++
"\n</ol>\n"
2010-04-10 12:38:07 -07:00
else do
modify $ \s -> s { stListLevel = stListLevel s ++ "#"
, stStartNum = if start > 1
then Just start
else Nothing }
level <- gets $ length . stListLevel
2010-04-10 12:38:07 -07:00
contents <- mapM (listItemToTextile opts) items
modify $ \s -> s { stListLevel = init (stListLevel s),
stStartNum = Nothing }
return $ vcat contents ++ (if level > 1 then "" else "\n")
2010-04-10 12:38:07 -07:00
blockToTextile opts (DefinitionList items) = do
contents <- withUseTags $ mapM (definitionListItemToTextile opts) items
return $ "<dl>\n" ++ vcat contents ++ "\n</dl>\n"
2010-04-10 12:38:07 -07:00
-- Auxiliary functions for lists:
-- | Convert ordered list attributes to HTML attribute string
listAttribsToString :: ListAttributes -> String
listAttribsToString (startnum, numstyle, _) =
let numstyle' = camelCaseToHyphenated $ show numstyle
in (if startnum /= 1
then " start=\"" ++ show startnum ++ "\""
else "") ++
(if numstyle /= DefaultStyle
then " style=\"list-style-type: " ++ numstyle' ++ ";\""
else "")
-- | Convert bullet or ordered list item (list of blocks) to Textile.
listItemToTextile :: PandocMonad m
=> WriterOptions -> [Block] -> TW m String
2010-04-10 12:38:07 -07:00
listItemToTextile opts items = do
contents <- blockListToTextile opts items
useTags <- gets stUseTags
2010-04-10 12:38:07 -07:00
if useTags
then return $ "<li>" ++ contents ++ "</li>"
2010-04-10 12:38:07 -07:00
else do
marker <- gets stListLevel
mbstart <- gets stStartNum
case mbstart of
Just n -> do
modify $ \s -> s{ stStartNum = Nothing }
return $ marker ++ show n ++ " " ++ contents
Nothing -> return $ marker ++ " " ++ contents
2010-04-10 12:38:07 -07:00
-- | Convert definition list item (label, list of blocks) to Textile.
definitionListItemToTextile :: PandocMonad m
=> WriterOptions
2012-07-26 22:32:53 -07:00
-> ([Inline],[[Block]])
-> TW m String
2010-04-10 12:38:07 -07:00
definitionListItemToTextile opts (label, items) = do
labelText <- inlineListToTextile opts label
contents <- mapM (blockListToTextile opts) items
return $ "<dt>" ++ labelText ++ "</dt>\n" ++
(intercalate "\n" $ map (\d -> "<dd>" ++ d ++ "</dd>") contents)
2010-04-10 12:38:07 -07:00
-- | True if the list can be handled by simple wiki markup, False if HTML tags will be needed.
isSimpleList :: Block -> Bool
isSimpleList x =
case x of
BulletList items -> all isSimpleListItem items
OrderedList (_, sty, _) items -> all isSimpleListItem items &&
sty `elem` [DefaultStyle, Decimal]
2010-04-10 12:38:07 -07:00
_ -> False
-- | True if list item can be handled with the simple wiki syntax. False if
-- HTML tags will be needed.
isSimpleListItem :: [Block] -> Bool
isSimpleListItem [] = True
isSimpleListItem [x] =
case x of
Plain _ -> True
Para _ -> True
BulletList _ -> isSimpleList x
OrderedList _ _ -> isSimpleList x
_ -> False
2010-04-10 12:38:07 -07:00
isSimpleListItem [x, y] | isPlainOrPara x =
case y of
BulletList _ -> isSimpleList y
OrderedList _ _ -> isSimpleList y
_ -> False
2010-04-10 12:38:07 -07:00
isSimpleListItem _ = False
isPlainOrPara :: Block -> Bool
isPlainOrPara (Plain _) = True
isPlainOrPara (Para _) = True
isPlainOrPara _ = False
-- | Concatenates strings with line breaks between them.
vcat :: [String] -> String
vcat = intercalate "\n"
-- Auxiliary functions for tables. (TODO: these are common to HTML, MediaWiki,
-- and Textile writers, and should be abstracted out.)
tableRowToTextile :: PandocMonad m
=> WriterOptions
-> [String]
-> Int
-> [[Block]]
-> TW m String
2010-04-10 12:38:07 -07:00
tableRowToTextile opts alignStrings rownum cols' = do
let celltype = if rownum == 0 then "th" else "td"
let rowclass = case rownum of
0 -> "header"
2010-04-10 12:38:07 -07:00
x | x `rem` 2 == 1 -> "odd"
_ -> "even"
2012-07-26 22:32:53 -07:00
cols'' <- sequence $ zipWith
(\alignment item -> tableItemToTextile opts celltype alignment item)
2010-04-10 12:38:07 -07:00
alignStrings cols'
return $ "<tr class=\"" ++ rowclass ++ "\">\n" ++ unlines cols'' ++ "</tr>"
alignmentToString :: Alignment -> [Char]
alignmentToString alignment = case alignment of
AlignLeft -> "left"
AlignRight -> "right"
AlignCenter -> "center"
AlignDefault -> "left"
tableItemToTextile :: PandocMonad m
=> WriterOptions
-> String
-> String
-> [Block]
-> TW m String
2010-04-10 12:38:07 -07:00
tableItemToTextile opts celltype align' item = do
let mkcell x = "<" ++ celltype ++ " align=\"" ++ align' ++ "\">" ++
x ++ "</" ++ celltype ++ ">"
contents <- blockListToTextile opts item
return $ mkcell contents
-- | Convert list of Pandoc block elements to Textile.
blockListToTextile :: PandocMonad m
=> WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
-> TW m String
2010-04-10 12:38:07 -07:00
blockListToTextile opts blocks =
mapM (blockToTextile opts) blocks >>= return . vcat
-- | Convert list of Pandoc inline elements to Textile.
inlineListToTextile :: PandocMonad m
=> WriterOptions -> [Inline] -> TW m String
2010-04-10 12:38:07 -07:00
inlineListToTextile opts lst =
mapM (inlineToTextile opts) lst >>= return . concat
-- | Convert Pandoc inline element to Textile.
inlineToTextile :: PandocMonad m => WriterOptions -> Inline -> TW m String
2010-04-10 12:38:07 -07:00
inlineToTextile opts (Span _ lst) =
inlineListToTextile opts lst
2012-07-26 22:32:53 -07:00
inlineToTextile opts (Emph lst) = do
2010-04-10 12:38:07 -07:00
contents <- inlineListToTextile opts lst
return $ if '_' `elem` contents
then "<em>" ++ contents ++ "</em>"
2012-07-26 22:32:53 -07:00
else "_" ++ contents ++ "_"
2010-04-10 12:38:07 -07:00
inlineToTextile opts (Strong lst) = do
contents <- inlineListToTextile opts lst
return $ if '*' `elem` contents
then "<strong>" ++ contents ++ "</strong>"
else "*" ++ contents ++ "*"
inlineToTextile opts (Strikeout lst) = do
contents <- inlineListToTextile opts lst
return $ if '-' `elem` contents
then "<del>" ++ contents ++ "</del>"
else "-" ++ contents ++ "-"
inlineToTextile opts (Superscript lst) = do
contents <- inlineListToTextile opts lst
return $ if '^' `elem` contents
then "<sup>" ++ contents ++ "</sup>"
else "[^" ++ contents ++ "^]"
2010-04-10 12:38:07 -07:00
inlineToTextile opts (Subscript lst) = do
contents <- inlineListToTextile opts lst
return $ if '~' `elem` contents
then "<sub>" ++ contents ++ "</sub>"
else "[~" ++ contents ++ "~]"
2010-04-10 12:38:07 -07:00
inlineToTextile opts (SmallCaps lst) = inlineListToTextile opts lst
inlineToTextile opts (Quoted SingleQuote lst) = do
contents <- inlineListToTextile opts lst
return $ "'" ++ contents ++ "'"
inlineToTextile opts (Quoted DoubleQuote lst) = do
contents <- inlineListToTextile opts lst
return $ "\"" ++ contents ++ "\""
inlineToTextile opts (Cite _ lst) = inlineListToTextile opts lst
inlineToTextile _ (Code _ str) =
2010-04-10 12:38:07 -07:00
return $ if '@' `elem` str
then "<tt>" ++ escapeStringForXML str ++ "</tt>"
2012-07-26 22:32:53 -07:00
else "@" ++ str ++ "@"
2010-04-10 12:38:07 -07:00
inlineToTextile _ (Str str) = return $ escapeStringForTextile str
inlineToTextile _ (Math _ str) =
return $ "<span class=\"math\">" ++ escapeStringForXML str ++ "</math>"
inlineToTextile opts il@(RawInline f str)
2013-08-10 17:23:51 -07:00
| f == Format "html" || f == Format "textile" = return str
| (f == Format "latex" || f == Format "tex") &&
isEnabled Ext_raw_tex opts = return str
| otherwise = do
report $ InlineNotRendered il
return ""
2010-04-10 12:38:07 -07:00
inlineToTextile _ LineBreak = return "\n"
inlineToTextile _ SoftBreak = return " "
2010-04-10 12:38:07 -07:00
inlineToTextile _ Space = return " "
inlineToTextile opts (Link (_, cls, _) txt (src, _)) = do
let classes = if null cls
then ""
else "(" ++ unwords cls ++ ")"
2010-04-10 12:38:07 -07:00
label <- case txt of
[Code _ s]
| s == src -> return "$"
[Str s]
| s == src -> return "$"
_ -> inlineListToTextile opts txt
return $ "\"" ++ classes ++ label ++ "\":" ++ src
2010-04-10 12:38:07 -07:00
inlineToTextile opts (Image attr@(_, cls, _) alt (source, tit)) = do
2010-04-10 12:38:07 -07:00
alt' <- inlineListToTextile opts alt
let txt = if null tit
then if null alt'
then ""
else "(" ++ alt' ++ ")"
else "(" ++ tit ++ ")"
classes = if null cls
then ""
else "(" ++ unwords cls ++ ")"
showDim dir = let toCss str = Just $ show dir ++ ":" ++ str ++ ";"
in case (dimension dir attr) of
Just (Percent a) -> toCss $ show (Percent a)
Just dim -> toCss $ showInPixel opts dim ++ "px"
Nothing -> Nothing
styles = case (showDim Width, showDim Height) of
(Just w, Just h) -> "{" ++ w ++ h ++ "}"
(Just w, Nothing) -> "{" ++ w ++ "height:auto;}"
(Nothing, Just h) -> "{" ++ "width:auto;" ++ h ++ "}"
(Nothing, Nothing) -> ""
return $ "!" ++ classes ++ styles ++ source ++ txt ++ "!"
2010-04-10 12:38:07 -07:00
inlineToTextile opts (Note contents) = do
curNotes <- gets stNotes
2010-04-10 12:38:07 -07:00
let newnum = length curNotes + 1
contents' <- blockListToTextile opts contents
let thisnote = "fn" ++ show newnum ++ ". " ++ contents' ++ "\n"
modify $ \s -> s { stNotes = thisnote : curNotes }
return $ "[" ++ show newnum ++ "]"
-- note - may not work for notes with multiple blocks