aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs20
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs6
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs88
3 files changed, 77 insertions, 37 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 18e3113d3..ba25d8ad8 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -107,7 +107,7 @@ pBulletList = try $ do
-- treat it as a list item, though it's not valid xhtml...
skipMany nonItem
items <- manyTill (pInTags "li" block >>~ skipMany nonItem) (pCloses "ul")
- return [BulletList items]
+ return [BulletList $ map fixPlains items]
pOrderedList :: TagParser [Block]
pOrderedList = try $ do
@@ -138,7 +138,7 @@ pOrderedList = try $ do
-- treat it as a list item, though it's not valid xhtml...
skipMany nonItem
items <- manyTill (pInTags "li" block >>~ skipMany nonItem) (pCloses "ol")
- return [OrderedList (start, style, DefaultDelim) items]
+ return [OrderedList (start, style, DefaultDelim) $ map fixPlains items]
pDefinitionList :: TagParser [Block]
pDefinitionList = try $ do
@@ -154,7 +154,19 @@ pDefListItem = try $ do
defs <- many1 (try $ skipMany nonItem >> pInTags "dd" block)
skipMany nonItem
let term = intercalate [LineBreak] terms
- return (term, defs)
+ return (term, map fixPlains defs)
+
+fixPlains :: [Block] -> [Block]
+fixPlains bs = if any isParaish bs
+ then map plainToPara bs
+ else bs
+ where isParaish (Para _) = True
+ isParaish (CodeBlock _ _) = True
+ isParaish (Header _ _) = True
+ isParaish (BlockQuote _) = True
+ isParaish _ = False
+ plainToPara (Plain xs) = Para xs
+ plainToPara x = x
pRawTag :: TagParser String
pRawTag = do
@@ -358,7 +370,7 @@ pInlinesInTags :: String -> ([Inline] -> Inline)
-> TagParser [Inline]
pInlinesInTags tagtype f = do
contents <- pInTags tagtype inline
- return [f contents]
+ return [f $ normalizeSpaces contents]
pInTags :: String -> TagParser [a]
-> TagParser [a]
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 232f1793e..a4157da2f 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -805,7 +805,11 @@ nonbreakingSpace = char '~' >> return (Str "\160")
-- hard line break
linebreak :: GenParser Char st Inline
-linebreak = try (string "\\\\") >> return LineBreak
+linebreak = try $ do
+ string "\\\\"
+ optional $ bracketedText '[' ']' -- e.g. \\[10pt]
+ spaces
+ return LineBreak
str :: GenParser Char st Inline
str = many1 (noneOf specialChars) >>= return . Str
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 1a15adf7a..cf008bf6a 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -42,6 +42,9 @@ import System.FilePath (dropExtension)
data WriterState =
WriterState { stInNote :: Bool -- @True@ if we're in a note
+ , stInTable :: Bool -- @True@ if we're in a table
+ , stTableNotes :: [(Char, Doc)] -- List of markers, notes
+ -- in current table
, stOLLevel :: Int -- level of ordered list nesting
, stOptions :: WriterOptions -- writer options, so they don't have to be parameter
, stVerbInNote :: Bool -- true if document has verbatim text in note
@@ -59,7 +62,8 @@ data WriterState =
writeLaTeX :: WriterOptions -> Pandoc -> String
writeLaTeX options document =
evalState (pandocToLaTeX options document) $
- WriterState { stInNote = False, stOLLevel = 1, stOptions = options,
+ WriterState { stInNote = False, stInTable = False,
+ stTableNotes = [], stOLLevel = 1, stOptions = options,
stVerbInNote = False, stEnumerate = False,
stTable = False, stStrikeout = False, stSubscript = False,
stUrl = False, stGraphics = False,
@@ -269,47 +273,61 @@ blockToLaTeX (Header level lst) = do
5 -> headerWith "\\subparagraph" stuffing
_ -> txt $$ blankline
blockToLaTeX (Table caption aligns widths heads rows) = do
+ modify $ \s -> s{ stInTable = True, stTableNotes = [] }
headers <- if all null heads
then return empty
- else liftM ($$ "\\hline") $ (tableRowToLaTeX widths) heads
+ else liftM ($$ "\\ML")
+ $ (tableRowToLaTeX True aligns widths) heads
captionText <- inlineListToLaTeX $ deVerb caption
- rows' <- mapM (tableRowToLaTeX widths) rows
- let colDescriptors = concat $ zipWith toColDescriptor widths aligns
- let tableBody = text ("\\begin{tabular}{" ++ colDescriptors ++ "}") $$
- headers $$ vcat rows' $$ "\\end{tabular}"
- let centered txt = "\\begin{center}" $$ txt $$ "\\end{center}"
- modify $ \s -> s{ stTable = True }
- return $ if isEmpty captionText
- then centered tableBody $$ blankline
- else "\\begin{table}[h]" $$ centered tableBody $$
- inCmd "caption" captionText $$ "\\end{table}" $$ blankline
-
-toColDescriptor :: Double -> Alignment -> String
-toColDescriptor 0 align =
+ let capt = if isEmpty captionText
+ then empty
+ else text "caption = " <> captionText <> "," <> space
+ rows' <- mapM (tableRowToLaTeX False aligns widths) rows
+ let rows'' = intersperse ("\\\\\\noalign{\\medskip}") rows'
+ tableNotes <- liftM (reverse . stTableNotes) get
+ let toNote (marker, x) = "\\tnote" <> brackets (char marker) <>
+ braces (nest 2 x)
+ let notes = vcat $ map toNote tableNotes
+ let colDescriptors = text $ concat $ map toColDescriptor aligns
+ let tableBody =
+ ("\\ctable" <> brackets (capt <> text "pos = H, center, botcap"))
+ <> braces colDescriptors
+ $$ braces ("% notes" <> cr <> notes <> cr)
+ $$ braces (text "% rows" $$ "\\FL" $$
+ vcat (headers : rows'') $$ "\\LL" <> cr)
+ modify $ \s -> s{ stTable = True, stInTable = False, stTableNotes = [] }
+ return $ tableBody $$ blankline
+
+toColDescriptor :: Alignment -> String
+toColDescriptor align =
case align of
AlignLeft -> "l"
AlignRight -> "r"
AlignCenter -> "c"
AlignDefault -> "l"
-toColDescriptor width align = ">{\\PBS" ++
- (case align of
- AlignLeft -> "\\raggedright"
- AlignRight -> "\\raggedleft"
- AlignCenter -> "\\centering"
- AlignDefault -> "\\raggedright") ++
- "\\hspace{0pt}}p{" ++ printf "%.2f" width ++ "\\columnwidth}"
blockListToLaTeX :: [Block] -> State WriterState Doc
blockListToLaTeX lst = mapM blockToLaTeX lst >>= return . vcat
-tableRowToLaTeX :: [Double] -> [[Block]] -> State WriterState Doc
-tableRowToLaTeX widths cols = do
+tableRowToLaTeX :: Bool
+ -> [Alignment]
+ -> [Double]
+ -> [[Block]]
+ -> State WriterState Doc
+tableRowToLaTeX header aligns widths cols = do
renderedCells <- mapM blockListToLaTeX cols
- let toCell 0 c = c
- toCell w c = "\\parbox{" <> text (printf "%.2f" w) <>
- "\\columnwidth}{" <> c <> cr <> "}"
- let cells = zipWith toCell widths renderedCells
- return $ (hcat $ intersperse (" & ") cells) <> "\\\\"
+ let valign = text $ if header then "[b]" else "[t]"
+ let halign x = case x of
+ AlignLeft -> "\\raggedright"
+ AlignRight -> "\\raggedleft"
+ AlignCenter -> "\\centering"
+ AlignDefault -> "\\raggedright"
+ let toCell 0 _ c = c
+ toCell w a c = "\\parbox" <> valign <>
+ braces (text (printf "%.2f\\columnwidth" w)) <>
+ braces (halign a <> cr <> c <> cr)
+ let cells = zipWith3 toCell widths aligns renderedCells
+ return $ hcat $ intersperse (" & ") cells
listItemToLaTeX :: [Block] -> State WriterState Doc
listItemToLaTeX lst = blockListToLaTeX lst >>= return . (text "\\item" $$) .
@@ -412,9 +430,15 @@ inlineToLaTeX (Note contents) = do
modify (\s -> s{stInNote = True})
contents' <- blockListToLaTeX contents
modify (\s -> s {stInNote = False})
- -- note: a \n before } is needed when note ends with a Verbatim environment
- return $ "\\footnote" <> braces (nest 2 contents')
-
+ inTable <- liftM stInTable get
+ if inTable
+ then do
+ curnotes <- liftM stTableNotes get
+ let marker = cycle ['a'..'z'] !! length curnotes
+ modify $ \s -> s{ stTableNotes = (marker, contents') : curnotes }
+ return $ "\\tmark" <> brackets (char marker) <> space
+ else return $ "\\footnote" <> braces (nest 2 contents')
+ -- note: a \n before } needed when note ends with a Verbatim environment
citationsToNatbib :: [Citation] -> State WriterState Doc
citationsToNatbib (one:[])