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/Creole.hs12
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs5
-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/FB2.hs32
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs55
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs4
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs18
9 files changed, 65 insertions, 84 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/Creole.hs b/src/Text/Pandoc/Readers/Creole.hs
index 4da259c0e..b4eb6eaef 100644
--- a/src/Text/Pandoc/Readers/Creole.hs
+++ b/src/Text/Pandoc/Readers/Creole.hs
@@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
License : GNU GPL, version 2 or above
Maintainer : Sascha Wilde <wilde@sha-bang.de>
- Stability : WIP
+ Stability : alpha
Portability : portable
Conversion of creole text to 'Pandoc' document.
@@ -64,7 +64,7 @@ readCreole opts s = do
type CRLParser = ParserT [Char] ParserState
--
--- Utility funcitons
+-- Utility functions
--
(<+>) :: (Monad m, Monoid a) => m a -> m a -> m a
@@ -111,7 +111,8 @@ block = do
return res
nowiki :: PandocMonad m => CRLParser m B.Blocks
-nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart >> manyTill content nowikiEnd)
+nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart
+ >> manyTill content nowikiEnd)
where
content = brackets <|> line
brackets = try $ option "" ((:[]) <$> newline)
@@ -154,7 +155,8 @@ listItem :: PandocMonad m => Char -> Int -> CRLParser m B.Blocks
listItem c n =
fmap (B.plain . B.trimInlines .mconcat) (listStart >> many1Till inline itemEnd)
where
- listStart = try $ optional newline >> skipSpaces >> count n (char c)
+ listStart = try $ skipSpaces >> optional newline >> skipSpaces
+ >> count n (char c)
>> lookAhead (noneOf [c]) >> skipSpaces
itemEnd = endOfParaElement <|> nextItem n
<|> if n < 3 then nextItem (n+1)
@@ -193,7 +195,7 @@ endOfParaElement = lookAhead $ endOfInput <|> endOfPara
startOf :: PandocMonad m => CRLParser m a -> CRLParser m ()
startOf p = try $ blankline >> p >> return mempty
startOfList = startOf $ anyList 1
- startOfTable =startOf table
+ startOfTable = startOf table
startOfHeader = startOf header
startOfNowiki = startOf nowiki
hr = startOf horizontalRule
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 8d37deb26..915fa852f 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -1172,8 +1172,9 @@ htmlTag f = try $ do
case next of
TagComment s
| "<!--" `isPrefixOf` inp -> do
- char '<'
- manyTill anyChar endAngle
+ string "<!--"
+ count (length s) anyChar
+ string "-->"
stripComments <- getOption readerStripComments
if stripComments
then return (next, "")
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/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index cf96393ca..666b67e52 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -64,7 +64,6 @@ data FbRenderState = FbRenderState
{ footnotes :: [ (Int, String, [Content]) ] -- ^ #, ID, text
, imagesToFetch :: [ (String, String) ] -- ^ filename, URL or path
, parentListMarker :: String -- ^ list marker of the parent ordered list
- , parentBulletLevel :: Int -- ^ nesting level of the unordered list
, writerOptions :: WriterOptions
} deriving (Show)
@@ -73,7 +72,7 @@ type FBM m = StateT FbRenderState m
newFB :: FbRenderState
newFB = FbRenderState { footnotes = [], imagesToFetch = []
- , parentListMarker = "", parentBulletLevel = 0
+ , parentListMarker = ""
, writerOptions = def }
data ImageMode = NormalImage | InlineImage deriving (Eq)
@@ -347,32 +346,21 @@ blockToXml (OrderedList a bss) = do
concat <$> zipWithM mkitem markers bss
blockToXml (BulletList bss) = do
state <- get
- let level = parentBulletLevel state
let pmrk = parentListMarker state
- let prefix = replicate (length pmrk) ' '
- let bullets = ["\x2022", "\x25e6", "*", "\x2043", "\x2023"]
- let mrk = prefix ++ bullets !! (level `mod` length bullets)
+ let mrk = pmrk ++ "•"
let mkitem bs = do
- modify (\s -> s { parentBulletLevel = level+1 })
+ modify (\s -> s { parentListMarker = mrk ++ " "})
item <- cMapM blockToXml $ plainToPara $ indentBlocks (mrk ++ " ") bs
- modify (\s -> s { parentBulletLevel = level }) -- restore bullet level
+ modify (\s -> s { parentListMarker = pmrk }) -- old parent marker
return item
cMapM mkitem bss
blockToXml (DefinitionList defs) =
cMapM mkdef defs
where
mkdef (term, bss) = do
- def' <- cMapM (cMapM blockToXml . sep . paraToPlain . map indent) bss
+ items <- cMapM (cMapM blockToXml . plainToPara . indentBlocks (replicate 4 ' ')) bss
t <- wrap "strong" term
- return [ el "p" t, el "p" def' ]
- sep blocks =
- if all needsBreak blocks then
- blocks ++ [Plain [LineBreak]]
- else
- blocks
- needsBreak (Para _) = False
- needsBreak (Plain ins) = LineBreak `notElem` ins
- needsBreak _ = True
+ return (el "p" t : items)
blockToXml h@Header{} = do
-- should not occur after hierarchicalize, except inside lists/blockquotes
report $ BlockNotRendered h
@@ -403,14 +391,6 @@ blockToXml (Table caption aligns _ headers rows) = do
align_str AlignDefault = "left"
blockToXml Null = return []
--- Replace paragraphs with plain text and line break.
--- Necessary to simulate multi-paragraph lists in FB2.
-paraToPlain :: [Block] -> [Block]
-paraToPlain [] = []
-paraToPlain (Para inlines : rest) =
- Plain inlines : Plain [LineBreak] : paraToPlain rest
-paraToPlain (p:rest) = p : paraToPlain rest
-
-- Replace plain text with paragraphs and add line break after paragraphs.
-- It is used to convert plain text from tight list items to paragraphs.
plainToPara :: [Block] -> [Block]
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index 2aac777c6..0ac37efba 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -37,7 +37,6 @@ import Data.Generics (everywhere, mkT)
import Data.List (isSuffixOf, partition)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
-import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.Highlighting (languages, languagesByExtension)
@@ -56,38 +55,14 @@ import qualified Text.XML.Light as Xml
data JATSVersion = JATS1_1
deriving (Eq, Show)
-type DB = ReaderT JATSVersion
-
--- | Convert list of authors to a docbook <author> section
-authorToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m B.Inlines
-authorToJATS opts name' = do
- name <- render Nothing <$> inlinesToJATS opts name'
- let colwidth = if writerWrapText opts == WrapAuto
- then Just $ writerColumns opts
- else Nothing
- return $ B.rawInline "docbook" $ render colwidth $
- if ',' `elem` name
- then -- last name first
- let (lastname, rest) = break (==',') name
- firstname = triml rest in
- inTagsSimple "firstname" (text $ escapeStringForXML firstname) <>
- inTagsSimple "surname" (text $ escapeStringForXML lastname)
- else -- last name last
- let namewords = words name
- lengthname = length namewords
- (firstname, lastname) = case lengthname of
- 0 -> ("","")
- 1 -> ("", name)
- n -> (unwords (take (n-1) namewords), last namewords)
- in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$
- inTagsSimple "surname" (text $ escapeStringForXML lastname)
+type JATS = ReaderT JATSVersion
writeJATS :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeJATS opts d =
runReaderT (docToJATS opts d) JATS1_1
-- | Convert Pandoc document to string in JATS format.
-docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> DB m Text
+docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> JATS m Text
docToJATS opts (Pandoc meta blocks) = do
let isBackBlock (Div ("refs",_,_) _) = True
isBackBlock _ = False
@@ -110,14 +85,12 @@ docToJATS opts (Pandoc meta blocks) = do
TopLevelChapter -> 0
TopLevelSection -> 1
TopLevelDefault -> 1
- auths' <- mapM (authorToJATS opts) $ docAuthors meta
- let meta' = B.setMeta "author" auths' meta
metadata <- metaToJSON opts
(fmap (render' . vcat) .
mapM (elementToJATS opts' startLvl) .
hierarchicalize)
(fmap render' . inlinesToJATS opts')
- meta'
+ meta
main <- (render' . vcat) <$>
mapM (elementToJATS opts' startLvl) elements
back <- (render' . vcat) <$>
@@ -132,7 +105,7 @@ docToJATS opts (Pandoc meta blocks) = do
Just tpl -> renderTemplate' tpl context
-- | Convert an Element to JATS.
-elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> DB m Doc
+elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> JATS m Doc
elementToJATS opts _ (Blk block) = blockToJATS opts block
elementToJATS opts lvl (Sec _ _num (id',_,kvs) title elements) = do
let idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')]
@@ -144,7 +117,7 @@ elementToJATS opts lvl (Sec _ _num (id',_,kvs) title elements) = do
inTagsSimple "title" title' $$ vcat contents
-- | Convert a list of Pandoc blocks to JATS.
-blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> DB m Doc
+blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> JATS m Doc
blocksToJATS opts = fmap vcat . mapM (blockToJATS opts)
-- | Auxiliary function to convert Plain block to Para.
@@ -155,13 +128,13 @@ plainToPara x = x
-- | Convert a list of pairs of terms and definitions into a list of
-- JATS varlistentrys.
deflistItemsToJATS :: PandocMonad m
- => WriterOptions -> [([Inline],[[Block]])] -> DB m Doc
+ => WriterOptions -> [([Inline],[[Block]])] -> JATS m Doc
deflistItemsToJATS opts items =
vcat <$> mapM (uncurry (deflistItemToJATS opts)) items
-- | Convert a term and a list of blocks into a JATS varlistentry.
deflistItemToJATS :: PandocMonad m
- => WriterOptions -> [Inline] -> [[Block]] -> DB m Doc
+ => WriterOptions -> [Inline] -> [[Block]] -> JATS m Doc
deflistItemToJATS opts term defs = do
term' <- inlinesToJATS opts term
def' <- blocksToJATS opts $ concatMap (map plainToPara) defs
@@ -171,7 +144,7 @@ deflistItemToJATS opts term defs = do
-- | Convert a list of lists of blocks to a list of JATS list items.
listItemsToJATS :: PandocMonad m
- => WriterOptions -> Maybe [String] -> [[Block]] -> DB m Doc
+ => WriterOptions -> Maybe [String] -> [[Block]] -> JATS m Doc
listItemsToJATS opts markers items =
case markers of
Nothing -> vcat <$> mapM (listItemToJATS opts Nothing) items
@@ -179,7 +152,7 @@ listItemsToJATS opts markers items =
-- | Convert a list of blocks into a JATS list item.
listItemToJATS :: PandocMonad m
- => WriterOptions -> Maybe String -> [Block] -> DB m Doc
+ => WriterOptions -> Maybe String -> [Block] -> JATS m Doc
listItemToJATS opts mbmarker item = do
contents <- blocksToJATS opts item
return $ inTagsIndented "list-item" $
@@ -187,7 +160,7 @@ listItemToJATS opts mbmarker item = do
$$ contents
-- | Convert a Pandoc block element to JATS.
-blockToJATS :: PandocMonad m => WriterOptions -> Block -> DB m Doc
+blockToJATS :: PandocMonad m => WriterOptions -> Block -> JATS m Doc
blockToJATS _ Null = return empty
-- Bibliography reference:
blockToJATS opts (Div ('r':'e':'f':'-':_,_,_) [Para lst]) =
@@ -311,7 +284,7 @@ tableRowToJATS :: PandocMonad m
=> WriterOptions
-> Bool
-> [[Block]]
- -> DB m Doc
+ -> JATS m Doc
tableRowToJATS opts isHeader cols =
(inTagsIndented "tr" . vcat) <$> mapM (tableItemToJATS opts isHeader) cols
@@ -319,17 +292,17 @@ tableItemToJATS :: PandocMonad m
=> WriterOptions
-> Bool
-> [Block]
- -> DB m Doc
+ -> JATS m Doc
tableItemToJATS opts isHeader item =
(inTags True (if isHeader then "th" else "td") [] . vcat) <$>
mapM (blockToJATS opts) item
-- | Convert a list of inline elements to JATS.
-inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m Doc
+inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> JATS m Doc
inlinesToJATS opts lst = hcat <$> mapM (inlineToJATS opts) lst
-- | Convert an inline element to JATS.
-inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> DB m Doc
+inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> JATS m Doc
inlineToJATS _ (Str str) = return $ text $ escapeStringForXML str
inlineToJATS opts (Emph lst) =
inTagsSimple "italic" <$> inlinesToJATS opts lst
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