aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/ImageSize.hs7
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs14
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs4
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs18
5 files changed, 35 insertions, 10 deletions
diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs
index 27d5c6a9c..5f491e08b 100644
--- a/src/Text/Pandoc/ImageSize.hs
+++ b/src/Text/Pandoc/ImageSize.hs
@@ -79,6 +79,7 @@ instance Show Direction where
data Dimension = Pixel Integer
| Centimeter Double
+ | Millimeter Double
| Inch Double
| Percent Double
| Em Double
@@ -86,6 +87,7 @@ data Dimension = Pixel Integer
instance Show Dimension where
show (Pixel a) = show a ++ "px"
show (Centimeter a) = showFl a ++ "cm"
+ show (Millimeter a) = showFl a ++ "mm"
show (Inch a) = showFl a ++ "in"
show (Percent a) = show a ++ "%"
show (Em a) = showFl a ++ "em"
@@ -184,6 +186,7 @@ inInch opts dim =
case dim of
(Pixel a) -> fromIntegral a / fromIntegral (writerDpi opts)
(Centimeter a) -> a * 0.3937007874
+ (Millimeter a) -> a * 0.03937007874
(Inch a) -> a
(Percent _) -> 0
(Em a) -> a * (11/64)
@@ -193,6 +196,7 @@ inPixel opts dim =
case dim of
(Pixel a) -> a
(Centimeter a) -> floor $ dpi * a * 0.3937007874 :: Integer
+ (Millimeter a) -> floor $ dpi * a * 0.03937007874 :: Integer
(Inch a) -> floor $ dpi * a :: Integer
(Percent _) -> 0
(Em a) -> floor $ dpi * a * (11/64) :: Integer
@@ -225,6 +229,7 @@ scaleDimension factor dim =
case dim of
Pixel x -> Pixel (round $ factor * fromIntegral x)
Centimeter x -> Centimeter (factor * x)
+ Millimeter x -> Millimeter (factor * x)
Inch x -> Inch (factor * x)
Percent x -> Percent (factor * x)
Em x -> Em (factor * x)
@@ -243,7 +248,7 @@ lengthToDim :: String -> Maybe Dimension
lengthToDim s = numUnit s >>= uncurry toDim
where
toDim a "cm" = Just $ Centimeter a
- toDim a "mm" = Just $ Centimeter (a / 10)
+ toDim a "mm" = Just $ Millimeter a
toDim a "in" = Just $ Inch a
toDim a "inch" = Just $ Inch a
toDim a "%" = Just $ Percent a
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index a982029af..9bac3d3a7 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1132,7 +1132,7 @@ inlineCommand' = try $ do
lookupListDefault raw names inlineCommands
tok :: PandocMonad m => LP m Inlines
-tok = grouped inline <|> inlineCommand' <|> singleChar'
+tok = try $ spaces >> grouped inline <|> inlineCommand' <|> singleChar'
where singleChar' = do
Tok _ _ t <- singleChar
return (str (T.unpack t))
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 2a88b39ec..98552e65d 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -846,6 +846,7 @@ listLine continuationIndent = try $ do
skipMany spaceChar
listStart)
notFollowedByHtmlCloser
+ notFollowedByDivCloser
optional (() <$ gobbleSpaces continuationIndent)
listLineCommon
@@ -883,16 +884,24 @@ listContinuation continuationIndent = try $ do
x <- try $ do
notFollowedBy blankline
notFollowedByHtmlCloser
+ notFollowedByDivCloser
gobbleSpaces continuationIndent
anyLineNewline
xs <- many $ try $ do
notFollowedBy blankline
notFollowedByHtmlCloser
+ notFollowedByDivCloser
gobbleSpaces continuationIndent <|> notFollowedBy' listStart
anyLineNewline
blanks <- many blankline
return $ concat (x:xs) ++ blanks
+notFollowedByDivCloser :: PandocMonad m => MarkdownParser m ()
+notFollowedByDivCloser = do
+ guardDisabled Ext_fenced_divs <|>
+ do divLevel <- stateFencedDivLevel <$> getState
+ guard (divLevel < 1) <|> notFollowedBy divFenceEnd
+
notFollowedByHtmlCloser :: PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser = do
inHtmlBlock <- stateInHtmlBlock <$> getState
@@ -965,6 +974,7 @@ defRawBlock compact = try $ do
let dline = try
( do notFollowedBy blankline
notFollowedByHtmlCloser
+ notFollowedByDivCloser
if compact -- laziness not compatible with compact
then () <$ indentSpaces
else (() <$ indentSpaces)
@@ -1688,10 +1698,8 @@ endline = try $ do
guardEnabled Ext_blank_before_header <|> (notFollowedBy . char =<< atxChar) -- atx header
guardDisabled Ext_backtick_code_blocks <|>
notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced))
- guardDisabled Ext_fenced_divs <|>
- do divLevel <- stateFencedDivLevel <$> getState
- guard (divLevel < 1) <|> notFollowedBy divFenceEnd
notFollowedByHtmlCloser
+ notFollowedByDivCloser
(eof >> return mempty)
<|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak))
<|> (guardEnabled Ext_ignore_line_breaks >> return mempty)
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ab1e90b3b..976450dcd 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -371,6 +371,10 @@ toSlides bs = do
concat `fmap` mapM (elementToBeamer slideLevel) (hierarchicalize bs')
elementToBeamer :: PandocMonad m => Int -> Element -> LW m [Block]
+elementToBeamer _slideLevel (Blk (Div attr bs)) = do
+ -- make sure we support "blocks" inside divs
+ bs' <- concat `fmap` mapM (elementToBeamer 0) (hierarchicalize bs)
+ return [Div attr bs']
elementToBeamer _slideLevel (Blk b) = return [b]
elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts)
| lvl > slideLevel = do
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 5d812b169..a1f30cb0e 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -397,11 +397,19 @@ blockToMarkdown' :: PandocMonad m
blockToMarkdown' _ Null = return empty
blockToMarkdown' opts (Div attrs ils) = do
contents <- blockListToMarkdown opts ils
- return $ if isEnabled Ext_raw_html opts &&
- isEnabled Ext_markdown_in_html_blocks opts
- then tagWithAttrs "div" attrs <> blankline <>
- contents <> blankline <> "</div>" <> blankline
- else contents <> blankline
+ return $
+ case () of
+ _ | isEnabled Ext_fenced_divs opts &&
+ attrs /= nullAttr ->
+ nowrap (text ":::" <+> attrsToMarkdown attrs) $$
+ chomp contents $$
+ text ":::" <> blankline
+ | isEnabled Ext_native_divs opts ||
+ (isEnabled Ext_raw_html opts &&
+ isEnabled Ext_markdown_in_html_blocks opts) ->
+ tagWithAttrs "div" attrs <> blankline <>
+ contents <> blankline <> "</div>" <> blankline
+ | otherwise -> contents <> blankline
blockToMarkdown' opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
-- escape if para starts with ordered list marker