aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Textile.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Textile.hs')
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs58
1 files changed, 44 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index df632adc6..98f9157fb 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -34,6 +34,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared
import Text.Pandoc.Pretty (render)
+import Text.Pandoc.ImageSize
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.XML ( escapeStringForXML )
@@ -44,6 +45,7 @@ import Data.Char ( isSpace )
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
, stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list
}
@@ -51,7 +53,8 @@ data WriterState = WriterState {
writeTextile :: WriterOptions -> Pandoc -> String
writeTextile opts document =
evalState (pandocToTextile opts document)
- WriterState { stNotes = [], stListLevel = [], stUseTags = False }
+ WriterState { stNotes = [], stListLevel = [], stStartNum = Nothing,
+ stUseTags = False }
-- | Return Textile representation of document.
pandocToTextile :: WriterOptions -> Pandoc -> State WriterState String
@@ -114,9 +117,9 @@ blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines
-- title beginning with fig: indicates that the image is a figure
-blockToTextile opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
+blockToTextile opts (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- blockToTextile opts (Para txt)
- im <- inlineToTextile opts (Image txt (src,tit))
+ im <- inlineToTextile opts (Image attr txt (src,tit))
return $ im ++ "\n" ++ capt
blockToTextile opts (Para inlines) = do
@@ -218,7 +221,7 @@ blockToTextile opts x@(BulletList items) = do
modify $ \s -> s { stListLevel = init (stListLevel s) }
return $ vcat contents ++ (if level > 1 then "" else "\n")
-blockToTextile opts x@(OrderedList attribs items) = do
+blockToTextile opts x@(OrderedList attribs@(start, _, _) items) = do
oldUseTags <- liftM stUseTags get
let useTags = oldUseTags || not (isSimpleList x)
if useTags
@@ -227,10 +230,14 @@ blockToTextile opts x@(OrderedList attribs items) = do
return $ "<ol" ++ listAttribsToString attribs ++ ">\n" ++ vcat contents ++
"\n</ol>\n"
else do
- modify $ \s -> s { stListLevel = stListLevel s ++ "#" }
+ modify $ \s -> s { stListLevel = stListLevel s ++ "#"
+ , stStartNum = if start > 1
+ then Just start
+ else Nothing }
level <- get >>= return . length . stListLevel
contents <- mapM (listItemToTextile opts) items
- modify $ \s -> s { stListLevel = init (stListLevel s) }
+ modify $ \s -> s { stListLevel = init (stListLevel s),
+ stStartNum = Nothing }
return $ vcat contents ++ (if level > 1 then "" else "\n")
blockToTextile opts (DefinitionList items) = do
@@ -258,8 +265,13 @@ listItemToTextile opts items = do
if useTags
then return $ "<li>" ++ contents ++ "</li>"
else do
- marker <- get >>= return . stListLevel
- return $ marker ++ " " ++ contents
+ 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
-- | Convert definition list item (label, list of blocks) to Textile.
definitionListItemToTextile :: WriterOptions
@@ -276,8 +288,8 @@ isSimpleList :: Block -> Bool
isSimpleList x =
case x of
BulletList items -> all isSimpleListItem items
- OrderedList (num, sty, _) items -> all isSimpleListItem items &&
- num == 1 && sty `elem` [DefaultStyle, Decimal]
+ OrderedList (_, sty, _) items -> all isSimpleListItem items &&
+ sty `elem` [DefaultStyle, Decimal]
_ -> False
-- | True if list item can be handled with the simple wiki syntax. False if
@@ -422,25 +434,43 @@ inlineToTextile opts (RawInline f str)
inlineToTextile _ (LineBreak) = return "\n"
+inlineToTextile _ SoftBreak = return " "
+
inlineToTextile _ Space = return " "
-inlineToTextile opts (Link txt (src, _)) = do
+inlineToTextile opts (Link (_, cls, _) txt (src, _)) = do
+ let classes = if null cls
+ then ""
+ else "(" ++ unwords cls ++ ")"
label <- case txt of
[Code _ s]
| s == src -> return "$"
[Str s]
| s == src -> return "$"
_ -> inlineListToTextile opts txt
- return $ "\"" ++ label ++ "\":" ++ src
+ return $ "\"" ++ classes ++ label ++ "\":" ++ src
-inlineToTextile opts (Image alt (source, tit)) = do
+inlineToTextile opts (Image attr@(_, cls, _) alt (source, tit)) = do
alt' <- inlineListToTextile opts alt
let txt = if null tit
then if null alt'
then ""
else "(" ++ alt' ++ ")"
else "(" ++ tit ++ ")"
- return $ "!" ++ source ++ txt ++ "!"
+ 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 ++ "!"
inlineToTextile opts (Note contents) = do
curNotes <- liftM stNotes get