summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Parsing.hs7
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs6
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs20
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs4
-rw-r--r--src/Text/Pandoc/Readers/Odt.hs44
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs114
-rw-r--r--src/Text/Pandoc/Readers/Odt/StyleReader.hs32
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs10
-rw-r--r--src/Text/Pandoc/Readers/RST.hs9
-rw-r--r--src/Text/Pandoc/Shared.hs35
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs8
-rw-r--r--src/Text/Pandoc/Writers/CommonMark.hs3
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs4
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs2
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs3
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs11
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs7
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs4
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs9
-rw-r--r--src/Text/Pandoc/Writers/Haddock.hs2
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs6
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Writers/Man.hs3
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs58
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs3
-rw-r--r--src/Text/Pandoc/Writers/Native.hs2
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs2
-rw-r--r--src/Text/Pandoc/Writers/Org.hs13
-rw-r--r--src/Text/Pandoc/Writers/RST.hs11
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs2
-rw-r--r--src/Text/Pandoc/Writers/TEI.hs15
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs3
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs3
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs6
34 files changed, 330 insertions, 133 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index e45e2247d..daf8e867d 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -718,11 +718,14 @@ lineBlockLine = try $ do
continuations <- many (try $ char ' ' >> anyLine)
return $ white ++ unwords (line : continuations)
+blankLineBlockLine :: Stream [Char] m Char => ParserT [Char] st m Char
+blankLineBlockLine = try (char '|' >> blankline)
+
-- | Parses an RST-style line block and returns a list of strings.
lineBlockLines :: Stream [Char] m Char => ParserT [Char] st m [String]
lineBlockLines = try $ do
- lines' <- many1 lineBlockLine
- skipMany1 $ blankline <|> try (char '|' >> blankline)
+ lines' <- many1 (lineBlockLine <|> ((:[]) <$> blankLineBlockLine))
+ skipMany1 $ blankline <|> blankLineBlockLine
return lines'
-- | Parse a table using 'headerParser', 'rowParser',
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 336b40933..4d8d5ab94 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -592,8 +592,6 @@ checkInMeta p = do
when accepts p
return mempty
-
-
addMeta :: ToMetaValue a => String -> a -> DB ()
addMeta field val = modify (setMeta field val)
@@ -612,7 +610,7 @@ isBlockElement (Elem e) = qName (elName e) `elem` blocktags
"important","caution","note","tip","warning","qandadiv",
"question","answer","abstract","itemizedlist","orderedlist",
"variablelist","article","book","table","informaltable",
- "informalexample",
+ "informalexample", "linegroup",
"screen","programlisting","example","calloutlist"]
isBlockElement _ = False
@@ -779,6 +777,7 @@ parseBlock (Elem e) =
"informaltable" -> parseTable
"informalexample" -> divWith ("", ["informalexample"], []) <$>
getBlocks e
+ "linegroup" -> lineBlock <$> lineItems
"literallayout" -> codeBlockWithLang
"screen" -> codeBlockWithLang
"programlisting" -> codeBlockWithLang
@@ -900,6 +899,7 @@ parseBlock (Elem e) =
let ident = attrValue "id" e
modify $ \st -> st{ dbSectionLevel = n - 1 }
return $ headerWith (ident,[],[]) n' headerText <> b
+ lineItems = mapM getInlines $ filterChildren (named "line") e
metaBlock = acceptingMetadata (getBlocks e) >> return mempty
getInlines :: Element -> DB Inlines
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index b9021ec08..7b9779105 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -65,7 +65,7 @@ import Control.Monad.State
import Control.Applicative ((<|>))
import qualified Data.Map as M
import Control.Monad.Except
-import Text.Pandoc.Shared (safeRead)
+import Text.Pandoc.Shared (safeRead, filteredFilesFromArchive)
import Text.TeXMath.Readers.OMML (readOMML)
import Text.Pandoc.Readers.Docx.Fonts (getUnicode, Font(..))
import Text.TeXMath (Exp)
@@ -86,7 +86,6 @@ data ReaderEnv = ReaderEnv { envNotes :: Notes
data ReaderState = ReaderState { stateWarnings :: [String] }
deriving Show
-
data DocxError = DocxError | WrongElem
deriving Show
@@ -276,7 +275,7 @@ archiveToDocxWithWarnings archive = do
comments = archiveToComments archive
numbering = archiveToNumbering archive
rels = archiveToRelationships archive
- media = archiveToMedia archive
+ media = filteredFilesFromArchive archive filePathIsMedia
(styles, parstyles) = archiveToStyles archive
rEnv =
ReaderEnv notes comments numbering rels media Nothing styles parstyles InDocument
@@ -402,7 +401,6 @@ archiveToComments zf =
case cmts of
Just c -> Comments cmts_namespaces c
Nothing -> Comments cmts_namespaces M.empty
-
filePathToRelType :: FilePath -> Maybe DocumentLocation
filePathToRelType "word/_rels/document.xml.rels" = Just InDocument
@@ -424,7 +422,7 @@ filePathToRelationships ar fp | Just relType <- filePathToRelType fp
, Just relElems <- (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry =
mapMaybe (relElemToRelationship relType) $ elChildren relElems
filePathToRelationships _ _ = []
-
+
archiveToRelationships :: Archive -> [Relationship]
archiveToRelationships archive =
concatMap (filePathToRelationships archive) $ filesInArchive archive
@@ -435,16 +433,6 @@ filePathIsMedia fp =
in
(dir == "word/media/")
-getMediaPair :: Archive -> FilePath -> Maybe (FilePath, B.ByteString)
-getMediaPair zf fp =
- case findEntryByPath fp zf of
- Just e -> Just (fp, fromEntry e)
- Nothing -> Nothing
-
-archiveToMedia :: Archive -> Media
-archiveToMedia zf =
- mapMaybe (getMediaPair zf) (filter filePathIsMedia (filesInArchive zf))
-
lookupLevel :: String -> String -> Numbering -> Maybe Level
lookupLevel numId ilvl (Numbering _ numbs absNumbs) = do
absNumId <- lookup numId $ map (\(Numb nid absnumid) -> (nid, absnumid)) numbs
@@ -741,7 +729,7 @@ elemToCommentStart ns element
, Just cmtDate <- findAttr (elemName ns "w" "date") element = do
bps <- mapD (elemToBodyPart ns) (elChildren element)
return $ CommentStart cmtId cmtAuthor cmtDate bps
-elemToCommentStart _ _ = throwError WrongElem
+elemToCommentStart _ _ = throwError WrongElem
lookupFootnote :: String -> Notes -> Maybe Element
lookupFootnote s (Notes _ fns _) = fns >>= (M.lookup s)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 2e95c518d..68bc936b1 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -32,7 +32,7 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.
module Text.Pandoc.Readers.Markdown ( readMarkdown,
readMarkdownWithWarnings ) where
-import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate )
+import Data.List ( transpose, sortBy, findIndex, intercalate )
import qualified Data.Map as M
import Data.Scientific (coefficient, base10Exponent)
import Data.Ord ( comparing )
@@ -1106,7 +1106,7 @@ lineBlock = try $ do
guardEnabled Ext_line_blocks
lines' <- lineBlockLines >>=
mapM (parseFromString (trimInlinesF . mconcat <$> many inline))
- return $ B.para <$> (mconcat $ intersperse (return B.linebreak) lines')
+ return $ B.lineBlock <$> sequence lines'
--
-- Tables
diff --git a/src/Text/Pandoc/Readers/Odt.hs b/src/Text/Pandoc/Readers/Odt.hs
index 68e89263c..046fb4d6d 100644
--- a/src/Text/Pandoc/Readers/Odt.hs
+++ b/src/Text/Pandoc/Readers/Odt.hs
@@ -37,6 +37,8 @@ import qualified Text.XML.Light as XML
import qualified Data.ByteString.Lazy as B
+import System.FilePath
+
import Text.Pandoc.Definition
import Text.Pandoc.Error
import Text.Pandoc.Options
@@ -48,39 +50,49 @@ import Text.Pandoc.Readers.Odt.StyleReader
import Text.Pandoc.Readers.Odt.Generic.XMLConverter
import Text.Pandoc.Readers.Odt.Generic.Fallible
+import Text.Pandoc.Shared (filteredFilesFromArchive)
--
readOdt :: ReaderOptions
-> B.ByteString
-> Either PandocError (Pandoc, MediaBag)
-readOdt _ bytes = case bytesToOdt bytes of
- Right pandoc -> Right (pandoc , mempty)
- Left err -> Left err
+readOdt _ bytes = bytesToOdt bytes-- of
+-- Right (pandoc, mediaBag) -> Right (pandoc , mediaBag)
+-- Left err -> Left err
--
-bytesToOdt :: B.ByteString -> Either PandocError Pandoc
+bytesToOdt :: B.ByteString -> Either PandocError (Pandoc, MediaBag)
bytesToOdt bytes = case toArchiveOrFail bytes of
Right archive -> archiveToOdt archive
Left _ -> Left $ ParseFailure "Couldn't parse odt file."
--
-archiveToOdt :: Archive -> Either PandocError Pandoc
+archiveToOdt :: Archive -> Either PandocError (Pandoc, MediaBag)
archiveToOdt archive
- | Just contentEntry <- findEntryByPath "content.xml" archive
- , Just stylesEntry <- findEntryByPath "styles.xml" archive
- , Just contentElem <- entryToXmlElem contentEntry
- , Just stylesElem <- entryToXmlElem stylesEntry
- , Right styles <- chooseMax (readStylesAt stylesElem )
- (readStylesAt contentElem)
- , startState <- readerState styles
- , Right pandoc <- runConverter' read_body
- startState
- contentElem
- = Right pandoc
+ | Just contentEntry <- findEntryByPath "content.xml" archive
+ , Just stylesEntry <- findEntryByPath "styles.xml" archive
+ , Just contentElem <- entryToXmlElem contentEntry
+ , Just stylesElem <- entryToXmlElem stylesEntry
+ , Right styles <- chooseMax (readStylesAt stylesElem )
+ (readStylesAt contentElem)
+ , media <- filteredFilesFromArchive archive filePathIsOdtMedia
+ , startState <- readerState styles media
+ , Right pandocWithMedia <- runConverter' read_body
+ startState
+ contentElem
+
+ = Right pandocWithMedia
| otherwise
-- Not very detailed, but I don't think more information would be helpful
= Left $ ParseFailure "Couldn't parse odt file."
+ where
+ filePathIsOdtMedia :: FilePath -> Bool
+ filePathIsOdtMedia fp =
+ let (dir, _) = splitFileName fp
+ in
+ (dir == "Pictures/")
+
--
entryToXmlElem :: Entry -> Maybe XML.Element
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index ffd2f61d1..0b152268f 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -42,6 +42,7 @@ module Text.Pandoc.Readers.Odt.ContentReader
import Control.Arrow
import Control.Applicative hiding ( liftA, liftA2, liftA3 )
+import qualified Data.ByteString.Lazy as B
import qualified Data.Map as M
import Data.List ( find )
import Data.Maybe
@@ -50,6 +51,7 @@ import qualified Text.XML.Light as XML
import Text.Pandoc.Definition
import Text.Pandoc.Builder
+import Text.Pandoc.MediaBag (insertMedia, MediaBag)
import Text.Pandoc.Shared
import Text.Pandoc.Readers.Odt.Base
@@ -68,6 +70,7 @@ import qualified Data.Set as Set
--------------------------------------------------------------------------------
type Anchor = String
+type Media = [(FilePath, B.ByteString)]
data ReaderState
= ReaderState { -- | A collection of styles read somewhere else.
@@ -87,14 +90,17 @@ data ReaderState
-- | A map from internal anchor names to "pretty" ones.
-- The mapping is a purely cosmetic one.
, bookmarkAnchors :: M.Map Anchor Anchor
-
+ -- | A map of files / binary data from the archive
+ , envMedia :: Media
+ -- | Hold binary resources used in the document
+ , odtMediaBag :: MediaBag
-- , sequences
-- , trackedChangeIDs
}
deriving ( Show )
-readerState :: Styles -> ReaderState
-readerState styles = ReaderState styles [] 0 Nothing M.empty
+readerState :: Styles -> Media -> ReaderState
+readerState styles media = ReaderState styles [] 0 Nothing M.empty media mempty
--
pushStyle' :: Style -> ReaderState -> ReaderState
@@ -134,6 +140,16 @@ putPrettyAnchor ugly pretty state@ReaderState{..}
usedAnchors :: ReaderState -> [Anchor]
usedAnchors ReaderState{..} = M.elems bookmarkAnchors
+getMediaBag :: ReaderState -> MediaBag
+getMediaBag ReaderState{..} = odtMediaBag
+
+getMediaEnv :: ReaderState -> Media
+getMediaEnv ReaderState{..} = envMedia
+
+insertMedia' :: (FilePath, B.ByteString) -> ReaderState -> ReaderState
+insertMedia' (fp, bs) state@ReaderState{..}
+ = state { odtMediaBag = insertMedia fp Nothing bs odtMediaBag }
+
--------------------------------------------------------------------------------
-- Reader type and associated tools
--------------------------------------------------------------------------------
@@ -190,6 +206,22 @@ popStyle = keepingTheValue (
getCurrentListLevel :: OdtReaderSafe _x ListLevel
getCurrentListLevel = getExtraState >>^ currentListLevel
+--
+updateMediaWithResource :: OdtReaderSafe (FilePath, B.ByteString) (FilePath, B.ByteString)
+updateMediaWithResource = keepingTheValue (
+ (keepingTheValue getExtraState
+ >>% insertMedia'
+ )
+ >>> setExtraState
+ )
+ >>^ fst
+
+lookupResource :: OdtReaderSafe String (FilePath, B.ByteString)
+lookupResource = proc target -> do
+ state <- getExtraState -< ()
+ case lookup target (getMediaEnv state) of
+ Just bs -> returnV (target, bs) -<< ()
+ Nothing -> returnV ("", B.empty) -< ()
type AnchorPrefix = String
@@ -386,7 +418,7 @@ getListConstructor ListLevelStyle{..} =
LltNumbered -> let listNumberStyle = toListNumberStyle listItemFormat
listNumberDelim = toListNumberDelim listItemPrefix
listItemSuffix
- in orderedListWith (1, listNumberStyle, listNumberDelim)
+ in orderedListWith (listItemStart, listNumberStyle, listNumberDelim)
where
toListNumberStyle LinfNone = DefaultStyle
toListNumberStyle LinfNumber = Decimal
@@ -511,6 +543,10 @@ read_plain_text = fst ^&&& read_plain_text' >>% recover
extractText (XML.Text cData) = succeedWith (XML.cdData cData)
extractText _ = failEmpty
+read_text_seq :: InlineMatcher
+read_text_seq = matchingElement NsText "sequence"
+ $ matchChildContent [] read_plain_text
+
-- specifically. I honor that, although the current implementation of '(<>)'
-- for 'Inlines' in "Text.Pandoc.Builder" will collaps them agein.
@@ -559,6 +595,8 @@ read_paragraph = matchingElement NsText "p"
, read_reference_start
, read_bookmark_ref
, read_reference_ref
+ , read_maybe_nested_img_frame
+ , read_text_seq
] read_plain_text
@@ -583,6 +621,7 @@ read_header = matchingElement NsText "h"
, read_reference_start
, read_bookmark_ref
, read_reference_ref
+ , read_maybe_nested_img_frame
] read_plain_text
) -< blocks
anchor <- getHeaderAnchor -< children
@@ -688,6 +727,64 @@ read_table_cell = matchingElement NsTable "table-cell"
]
----------------------
+-- Images
+----------------------
+
+--
+read_maybe_nested_img_frame :: InlineMatcher
+read_maybe_nested_img_frame = matchingElement NsDraw "frame"
+ $ proc blocks -> do
+ img <- (findChild' NsDraw "image") -< ()
+ case img of
+ Just _ -> read_frame -< blocks
+ Nothing -> matchChildContent' [ read_frame_text_box ] -< blocks
+
+read_frame :: OdtReaderSafe Inlines Inlines
+read_frame =
+ proc blocks -> do
+ w <- ( findAttr' NsSVG "width" ) -< ()
+ h <- ( findAttr' NsSVG "height" ) -< ()
+ titleNodes <- ( matchChildContent' [ read_frame_title ] ) -< blocks
+ src <- matchChildContent' [ read_image_src ] -< blocks
+ resource <- lookupResource -< src
+ _ <- updateMediaWithResource -< resource
+ alt <- (matchChildContent [] read_plain_text) -< blocks
+ arr (uncurry4 imageWith ) -<
+ (image_attributes w h, src, inlineListToIdentifier (toList titleNodes), alt)
+
+image_attributes :: Maybe String -> Maybe String -> Attr
+image_attributes x y =
+ ( "", [], (dim "width" x) ++ (dim "height" y))
+ where
+ dim _ (Just "") = []
+ dim name (Just v) = [(name, v)]
+ dim _ Nothing = []
+
+read_image_src :: (Namespace, ElementName, OdtReader Anchor Anchor)
+read_image_src = matchingElement NsDraw "image"
+ $ proc _ -> do
+ imgSrc <- findAttr NsXLink "href" -< ()
+ case imgSrc of
+ Right src -> returnV src -<< ()
+ Left _ -> returnV "" -< ()
+
+read_frame_title :: InlineMatcher
+read_frame_title = matchingElement NsSVG "title"
+ $ (matchChildContent [] read_plain_text)
+
+read_frame_text_box :: InlineMatcher
+read_frame_text_box = matchingElement NsDraw "text-box"
+ $ proc blocks -> do
+ paragraphs <- (matchChildContent' [ read_paragraph ]) -< blocks
+ arr read_img_with_caption -< toList paragraphs
+
+read_img_with_caption :: [Block] -> Inlines
+read_img_with_caption ((Para ((Image attr _ target) : txt)) : _) =
+ singleton (Image attr txt target) -- override caption with the text that follows
+read_img_with_caption _ =
+ mempty
+
+----------------------
-- Internal links
----------------------
@@ -782,8 +879,11 @@ read_text = matchChildContent' [ read_header
]
>>^ doc
-read_body :: OdtReader _x Pandoc
+read_body :: OdtReader _x (Pandoc, MediaBag)
read_body = executeIn NsOffice "body"
$ executeIn NsOffice "text"
- $ liftAsSuccess read_text
-
+ $ liftAsSuccess
+ $ proc inlines -> do
+ txt <- read_text -< inlines
+ state <- getExtraState -< ()
+ returnA -< (txt, getMediaBag state)
diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
index 96cfed0b3..26ba6df82 100644
--- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
@@ -76,8 +76,9 @@ import Control.Applicative hiding ( liftA, liftA2, liftA3 )
import qualified Data.Foldable as F
import qualified Data.Map as M
import qualified Data.Set as S
-import Data.List ( unfoldr )
+import Data.Char ( isDigit )
import Data.Default
+import Data.List ( unfoldr )
import Data.Maybe
import qualified Text.XML.Light as XML
@@ -390,6 +391,7 @@ data ListLevelStyle = ListLevelStyle { listLevelType :: ListLevelType
, listItemPrefix :: Maybe String
, listItemSuffix :: Maybe String
, listItemFormat :: ListItemNumberFormat
+ , listItemStart :: Int
}
deriving ( Eq, Ord )
@@ -578,25 +580,31 @@ readListLevelStyles namespace elementName levelType =
readListLevelStyle :: ListLevelType -> StyleReader _x (Int, ListLevelStyle)
readListLevelStyle levelType = readAttr NsText "level"
>>?! keepingTheValue
- ( liftA4 toListLevelStyle
- ( returnV levelType )
- ( findAttr' NsStyle "num-prefix" )
- ( findAttr' NsStyle "num-suffix" )
- ( getAttr NsStyle "num-format" )
+ ( liftA5 toListLevelStyle
+ ( returnV levelType )
+ ( findAttr' NsStyle "num-prefix" )
+ ( findAttr' NsStyle "num-suffix" )
+ ( getAttr NsStyle "num-format" )
+ ( findAttr' NsText "start-value" )
)
where
- toListLevelStyle _ p s LinfNone = ListLevelStyle LltBullet p s LinfNone
- toListLevelStyle _ p s f@(LinfString _) = ListLevelStyle LltBullet p s f
- toListLevelStyle t p s f = ListLevelStyle t p s f
+ toListLevelStyle _ p s LinfNone b = ListLevelStyle LltBullet p s LinfNone (startValue b)
+ toListLevelStyle _ p s f@(LinfString _) b = ListLevelStyle LltBullet p s f (startValue b)
+ toListLevelStyle t p s f b = ListLevelStyle t p s f (startValue b)
+ startValue (Just "") = 1
+ startValue (Just v) = if all isDigit v
+ then read v
+ else 1
+ startValue Nothing = 1
--
chooseMostSpecificListLevelStyle :: S.Set ListLevelStyle -> Maybe ListLevelStyle
chooseMostSpecificListLevelStyle ls | ls == mempty = Nothing
| otherwise = Just ( F.foldr1 select ls )
where
- select ( ListLevelStyle t1 p1 s1 f1 )
- ( ListLevelStyle t2 p2 s2 f2 )
- = ListLevelStyle (select' t1 t2) (p1 <|> p2) (s1 <|> s2) (selectLinf f1 f2)
+ select ( ListLevelStyle t1 p1 s1 f1 b1 )
+ ( ListLevelStyle t2 p2 s2 f2 _ )
+ = ListLevelStyle (select' t1 t2) (p1 <|> p2) (s1 <|> s2) (selectLinf f1 f2) b1
select' LltNumbered _ = LltNumbered
select' _ LltNumbered = LltNumbered
select' _ _ = LltBullet
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 82c3a6cbe..61978f79f 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -50,7 +50,7 @@ import Text.Pandoc.Shared ( compactify', compactify'DL )
import Control.Monad ( foldM, guard, mzero, void )
import Data.Char ( isSpace, toLower, toUpper)
-import Data.List ( foldl', intersperse, isPrefixOf )
+import Data.List ( foldl', isPrefixOf )
import Data.Maybe ( fromMaybe, isNothing )
import Data.Monoid ((<>))
@@ -288,9 +288,9 @@ blockAttributes = try $ do
let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv
let name = lookup "NAME" kv
let label = lookup "LABEL" kv
- caption' <- maybe (return Nothing)
- (fmap Just . parseFromString inlines)
- caption
+ caption' <- case caption of
+ Nothing -> return Nothing
+ Just s -> Just <$> parseFromString inlines (s ++ "\n")
kvAttrs' <- parseFromString keyValues . (++ "\n") $ fromMaybe mempty kvAttrs
return $ BlockAttributes
{ blockAttrName = name
@@ -427,7 +427,7 @@ verseBlock :: String -> OrgParser (F Blocks)
verseBlock blockType = try $ do
ignHeaders
content <- rawBlockContent blockType
- fmap B.para . mconcat . intersperse (pure B.linebreak)
+ fmap B.lineBlock . sequence
<$> mapM parseVerseLine (lines content)
where
-- replace initial spaces with nonbreaking spaces to preserve
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index f181d523a..1b06c6f23 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -39,7 +39,7 @@ import Text.Pandoc.Shared
import Text.Pandoc.Parsing
import Text.Pandoc.Options
import Control.Monad ( when, liftM, guard, mzero )
-import Data.List ( findIndex, intersperse, intercalate,
+import Data.List ( findIndex, intercalate,
transpose, sort, deleteFirstsBy, isSuffixOf , nub, union)
import Data.Maybe (fromMaybe)
import qualified Data.Map as M
@@ -228,7 +228,7 @@ lineBlock :: RSTParser Blocks
lineBlock = try $ do
lines' <- lineBlockLines
lines'' <- mapM parseInlineFromString lines'
- return $ B.para (mconcat $ intersperse B.linebreak lines'')
+ return $ B.lineBlock lines''
--
-- paragraph block
@@ -949,7 +949,8 @@ table = gridTable False <|> simpleTable False <|>
--
inline :: RSTParser Inlines
-inline = choice [ whitespace
+inline = choice [ note -- can start with whitespace, so try before ws
+ , whitespace
, link
, str
, endline
@@ -958,7 +959,6 @@ inline = choice [ whitespace
, code
, subst
, interpretedRole
- , note
, smart
, hyphens
, escapedChar
@@ -1174,6 +1174,7 @@ subst = try $ do
note :: RSTParser Inlines
note = try $ do
+ optional whitespace
ref <- noteMarker
char '_'
state <- getState
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 04752a194..4c10a5572 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -64,9 +64,11 @@ module Text.Pandoc.Shared (
compactify,
compactify',
compactify'DL,
+ linesToPara,
Element (..),
hierarchicalize,
uniqueIdent,
+ inlineListToIdentifier,
isHeaderBlock,
headerShift,
isTightList,
@@ -84,6 +86,7 @@ module Text.Pandoc.Shared (
fetchItem',
openURL,
collapseFilePath,
+ filteredFilesFromArchive,
-- * Error handling
err,
warn,
@@ -110,6 +113,7 @@ import System.Exit (exitWith, ExitCode(..))
import Data.Char ( toLower, isLower, isUpper, isAlpha,
isLetter, isDigit, isSpace )
import Data.List ( find, stripPrefix, intercalate )
+import Data.Maybe (mapMaybe)
import Data.Version ( showVersion )
import qualified Data.Map as M
import Network.URI ( escapeURIString, nonStrictRelativeTo,
@@ -152,7 +156,8 @@ import Paths_pandoc (getDataFileName)
#ifdef HTTP_CLIENT
import Network.HTTP.Client (httpLbs, responseBody, responseHeaders,
Request(port,host))
-import Network.HTTP.Client (parseRequest, newManager)
+import Network.HTTP.Client (parseRequest)
+import Network.HTTP.Client (newManager)
import Network.HTTP.Client.Internal (addProxy)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import System.Environment (getEnv)
@@ -630,6 +635,15 @@ compactify'DL items =
| otherwise -> items
_ -> items
+-- | Combine a list of lines by adding hard linebreaks.
+combineLines :: [[Inline]] -> [Inline]
+combineLines = intercalate [LineBreak]
+
+-- | Convert a list of lines into a paragraph with hard line breaks. This is
+-- useful e.g. for rudimentary support of LineBlock elements in writers.
+linesToPara :: [[Inline]] -> Block
+linesToPara = Para . combineLines
+
isPara :: Block -> Bool
isPara (Para _) = True
isPara _ = False
@@ -947,11 +961,7 @@ openURL u
in return $ Right (decodeLenient contents, Just mime)
#ifdef HTTP_CLIENT
| otherwise = withSocketsDo $ E.try $ do
-#if MIN_VERSION_http_client(0,4,30)
let parseReq = parseRequest
-#else
- let parseReq = parseUrl
-#endif
(proxy :: Either E.SomeException String) <- E.try $ getEnv "http_proxy"
req <- parseReq u
req' <- case proxy of
@@ -959,11 +969,7 @@ openURL u
Right pr -> (parseReq pr >>= \r ->
return $ addProxy (host r) (port r) req)
`mplus` return req
-#if MIN_VERSION_http_client(0,4,18)
resp <- newManager tlsManagerSettings >>= httpLbs req'
-#else
- resp <- withManager tlsManagerSettings $ httpLbs req'
-#endif
return (BS.concat $ toChunks $ responseBody resp,
UTF8.toString `fmap` lookup hContentType (responseHeaders resp))
#else
@@ -1028,6 +1034,16 @@ collapseFilePath = Posix.joinPath . reverse . foldl go [] . splitDirectories
isSingleton _ = Nothing
checkPathSeperator = fmap isPathSeparator . isSingleton
+--
+-- File selection from the archive
+--
+filteredFilesFromArchive :: Archive -> (FilePath -> Bool) -> [(FilePath, BL.ByteString)]
+filteredFilesFromArchive zf f =
+ mapMaybe (fileAndBinary zf) (filter f (filesInArchive zf))
+ where
+ fileAndBinary :: Archive -> FilePath -> Maybe (FilePath, BL.ByteString)
+ fileAndBinary a fp = findEntryByPath fp a >>= \e -> Just (fp, fromEntry e)
+
---
--- Squash blocks into inlines
---
@@ -1035,6 +1051,7 @@ collapseFilePath = Posix.joinPath . reverse . foldl go [] . splitDirectories
blockToInlines :: Block -> [Inline]
blockToInlines (Plain ils) = ils
blockToInlines (Para ils) = ils
+blockToInlines (LineBlock lns) = combineLines lns
blockToInlines (CodeBlock attr str) = [Code attr str]
blockToInlines (RawBlock fmt str) = [RawInline fmt str]
blockToInlines (BlockQuote blks) = blocksToInlines blks
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 0dfbd705e..c7097c368 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -137,6 +137,13 @@ blockToAsciiDoc opts (Para inlines) = do
then text "\\"
else empty
return $ esc <> contents <> blankline
+blockToAsciiDoc opts (LineBlock lns) = do
+ let docify line = if null line
+ then return blankline
+ else inlineListToAsciiDoc opts line
+ let joinWithLinefeeds = nowrap . mconcat . intersperse cr
+ contents <- joinWithLinefeeds <$> mapM docify lns
+ return $ "[verse]" $$ text "--" $$ contents $$ text "--" $$ blankline
blockToAsciiDoc _ (RawBlock f s)
| f == "asciidoc" = return $ text s
| otherwise = return empty
@@ -459,4 +466,3 @@ inlineToAsciiDoc opts (Span (ident,_,_) ils) = do
let identifier = if (null ident) then empty else ("[[" <> text ident <> "]]")
contents <- inlineListToAsciiDoc opts ils
return $ identifier <> contents
-
diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs
index 262f491a8..c6509fe92 100644
--- a/src/Text/Pandoc/Writers/CommonMark.hs
+++ b/src/Text/Pandoc/Writers/CommonMark.hs
@@ -33,7 +33,7 @@ module Text.Pandoc.Writers.CommonMark (writeCommonMark) where
import Text.Pandoc.Writers.HTML (writeHtmlString)
import Text.Pandoc.Definition
-import Text.Pandoc.Shared (isTightList)
+import Text.Pandoc.Shared (isTightList, linesToPara)
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options
@@ -94,6 +94,7 @@ blocksToNodes = foldr blockToNodes []
blockToNodes :: Block -> [Node] -> [Node]
blockToNodes (Plain xs) = (node PARAGRAPH (inlinesToNodes xs) :)
blockToNodes (Para xs) = (node PARAGRAPH (inlinesToNodes xs) :)
+blockToNodes (LineBlock lns) = blockToNodes $ linesToPara lns
blockToNodes (CodeBlock (_,classes,_) xs) =
(node (CODE_BLOCK (T.pack (unwords classes)) (T.pack xs)) [] :)
blockToNodes (RawBlock fmt xs)
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 8d54d62bd..398d4170f 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -163,6 +163,9 @@ blockToConTeXt (Para [Image attr txt (src,'f':'i':'g':':':_)]) = do
blockToConTeXt (Para lst) = do
contents <- inlineListToConTeXt lst
return $ contents <> blankline
+blockToConTeXt (LineBlock lns) = do
+ doclines <- nowrap . vcat <$> mapM inlineListToConTeXt lns
+ return $ "\\startlines" $$ doclines $$ "\\stoplines" <> blankline
blockToConTeXt (BlockQuote lst) = do
contents <- blockListToConTeXt lst
return $ "\\startblockquote" $$ nest 0 contents $$ "\\stopblockquote" <> blankline
@@ -467,4 +470,3 @@ fromBcp47 x = fromIso $ head x
fromIso "vi" = "vn"
fromIso "zh" = "cn"
fromIso l = l
-
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index d69eaaa64..631241724 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -227,6 +227,8 @@ blockToCustom lua (Para [Image attr txt (src,tit)]) =
blockToCustom lua (Para inlines) = callfunc lua "Para" inlines
+blockToCustom lua (LineBlock linesList) = callfunc lua "LineBlock" linesList
+
blockToCustom lua (RawBlock format str) =
callfunc lua "RawBlock" format str
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 8bb0810e4..e19b4666b 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -198,6 +198,8 @@ blockToDocbook opts (Para [Image attr txt (src,'f':'i':'g':':':_)]) =
blockToDocbook opts (Para lst)
| hasLineBreaks lst = flush $ nowrap $ inTagsSimple "literallayout" $ inlinesToDocbook opts lst
| otherwise = inTagsIndented "para" $ inlinesToDocbook opts lst
+blockToDocbook opts (LineBlock lns) =
+ blockToDocbook opts $ linesToPara lns
blockToDocbook opts (BlockQuote blocks) =
inTagsIndented "blockquote" $ blocksToDocbook opts blocks
blockToDocbook _ (CodeBlock (_,classes,_) str) =
@@ -385,4 +387,3 @@ idAndRole (id',cls,_) = ident ++ role
role = if null cls
then []
else [("role", unwords cls)]
-
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index a006773d6..dfa011784 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -275,7 +275,7 @@ writeDocx opts doc@(Pandoc meta _) = do
}
- ((contents, footnotes), st) <- runStateT
+ ((contents, footnotes), st) <- runStateT
(runReaderT
(writeOpenXML opts{writerWrapText = WrapNone} doc')
env)
@@ -446,7 +446,7 @@ writeDocx opts doc@(Pandoc meta _) = do
let newstyles = map newParaPropToOpenXml newDynamicParaProps ++
map newTextPropToOpenXml newDynamicTextProps ++
- (styleToOpenXml styleMaps $ writerHighlightStyle opts)
+ (styleToOpenXml styleMaps $ writerHighlightStyle opts)
let styledoc' = styledoc{ elContent = modifyContent (elContent styledoc) }
where
modifyContent
@@ -859,6 +859,7 @@ blockToOpenXML' opts (Para lst) = do
modify $ \s -> s { stFirstPara = False }
contents <- inlinesToOpenXML opts lst
return [mknode "w:p" [] (paraProps' ++ contents)]
+blockToOpenXML' opts (LineBlock lns) = blockToOpenXML opts $ linesToPara lns
blockToOpenXML' _ (RawBlock format str)
| format == Format "openxml" = return [ x | Elem x <- parseXML str ]
| otherwise = return []
@@ -1032,7 +1033,7 @@ setFirstPara = modify $ \s -> s { stFirstPara = True }
-- | Convert an inline element to OpenXML.
inlineToOpenXML :: WriterOptions -> Inline -> WS [Element]
-inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il
+inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il
inlineToOpenXML' :: WriterOptions -> Inline -> WS [Element]
inlineToOpenXML' _ (Str str) = formattedString str
@@ -1286,7 +1287,7 @@ withDirection x = do
textProps <- asks envTextProperties
-- We want to clean all bidirection (bidi) and right-to-left (rtl)
-- properties from the props first. This is because we don't want
- -- them to stack up.
+ -- them to stack up.
let paraProps' = filter (\e -> (qName . elName) e /= "bidi") paraProps
textProps' = filter (\e -> (qName . elName) e /= "rtl") textProps
if isRTL
@@ -1298,5 +1299,3 @@ withDirection x = do
else flip local x $ \env -> env { envParaProperties = paraProps'
, envTextProperties = textProps'
}
-
-
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 56e2b9027..402b74bc3 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -45,8 +45,8 @@ import Text.Pandoc.Options ( WriterOptions(
, writerStandalone
, writerTemplate
, writerWrapText), WrapOption(..) )
-import Text.Pandoc.Shared ( escapeURI, removeFormatting, camelCaseToHyphenated
- , trimr, normalize, substitute )
+import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting
+ , camelCaseToHyphenated, trimr, normalize, substitute )
import Text.Pandoc.Writers.Shared ( defField, metaToJSON )
import Text.Pandoc.ImageSize
import Text.Pandoc.Templates ( renderTemplate' )
@@ -147,6 +147,9 @@ blockToDokuWiki opts (Para inlines) = do
then "<HTML><p></HTML>" ++ contents ++ "<HTML></p></HTML>"
else contents ++ if null indent then "\n" else ""
+blockToDokuWiki opts (LineBlock lns) =
+ blockToDokuWiki opts $ linesToPara lns
+
blockToDokuWiki _ (RawBlock f str)
| f == Format "dokuwiki" = return str
-- See https://www.dokuwiki.org/wiki:syntax
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 80296e111..6f47dbcd2 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -46,7 +46,8 @@ import qualified Text.XML.Light.Cursor as XC
import Text.Pandoc.Definition
import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), def)
-import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize)
+import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize,
+ linesToPara)
-- | Data to be written at the end of the document:
-- (foot)notes, URLs, references, images.
@@ -323,6 +324,7 @@ blockToXml (RawBlock _ s) = return . spaceBeforeAfter .
map (el "p" . el "code") . lines $ s
blockToXml (Div _ bs) = cMapM blockToXml bs
blockToXml (BlockQuote bs) = liftM (list . el "cite") $ cMapM blockToXml bs
+blockToXml (LineBlock lns) = blockToXml $ linesToPara lns
blockToXml (OrderedList a bss) = do
state <- get
let pmrk = parentListMarker state
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index db8c301ef..2d0df4dbe 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -463,6 +463,13 @@ blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) = do
blockToHtml opts (Para lst) = do
contents <- inlineListToHtml opts lst
return $ H.p contents
+blockToHtml opts (LineBlock lns) =
+ if writerWrapText opts == WrapNone
+ then blockToHtml opts $ linesToPara lns
+ else do
+ let lf = preEscapedString "\n"
+ htmlLines <- mconcat . intersperse lf <$> mapM (inlineListToHtml opts) lns
+ return $ H.div ! A.style "white-space: pre-line;" $ htmlLines
blockToHtml opts (Div attr@(ident, classes, kvs) bs) = do
let speakerNotes = "notes" `elem` classes
-- we don't want incremental output inside speaker notes, see #1394
@@ -807,7 +814,7 @@ inlineToHtml opts inline =
let brtag = if writerHtml5 opts then H5.br else H.br
return $ case t of
InlineMath -> m
- DisplayMath -> brtag >> m >> brtag
+ DisplayMath -> brtag >> m >> brtag
(RawInline f str)
| f == Format "html" -> return $ preEscapedString str
| otherwise -> return mempty
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index 2e5f2dd08..caf549916 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -108,6 +108,8 @@ blockToHaddock opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) =
blockToHaddock opts (Para inlines) =
-- TODO: if it contains linebreaks, we need to use a @...@ block
(<> blankline) `fmap` blockToHaddock opts (Plain inlines)
+blockToHaddock opts (LineBlock lns) =
+ blockToHaddock opts $ linesToPara lns
blockToHaddock _ (RawBlock f str)
| f == "haddock" = do
return $ text str <> text "\n"
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 57a61178e..8f6123e20 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -2,7 +2,7 @@
{- |
Module : Text.Pandoc.Writers.ICML
- Copyright : Copyright (C) 2013 github.com/mb21
+ Copyright : Copyright (C) 2013-2016 github.com/mb21
License : GNU GPL, version 2 or above
Stability : alpha
@@ -18,7 +18,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.XML
import Text.Pandoc.Readers.TeXMath (texMathToInlines)
import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Shared (splitBy, fetchItem, warn)
+import Text.Pandoc.Shared (linesToPara, splitBy, fetchItem, warn)
import Text.Pandoc.Options
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Pretty
@@ -297,6 +297,8 @@ blockToICML opts style (Para img@[Image _ txt (_,'f':'i':'g':':':_)]) = do
caption <- parStyle opts (imgCaptionName:style) txt
return $ intersperseBrs [figure, caption]
blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) lst
+blockToICML opts style (LineBlock lns) =
+ blockToICML opts style $ linesToPara lns
blockToICML opts style (CodeBlock _ str) = parStyle opts (codeBlockName:style) $ [Str str]
blockToICML _ _ (RawBlock f str)
| f == Format "icml" = return $ text str
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index a88ff303f..517460f5d 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -437,6 +437,8 @@ blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do
else inlineListToLaTeX [Str ".",Space,Str ".",Space,Str "."]
blockToLaTeX (Para lst) =
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
+blockToLaTeX (LineBlock lns) = do
+ blockToLaTeX $ linesToPara lns
blockToLaTeX (BlockQuote lst) = do
beamer <- writerBeamer `fmap` gets stOptions
case lst of
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index caf26d515..159e89308 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -171,6 +171,8 @@ blockToMan opts (Para inlines) = do
contents <- liftM vcat $ mapM (inlineListToMan opts) $
splitSentences inlines
return $ text ".PP" $$ contents
+blockToMan opts (LineBlock lns) =
+ blockToMan opts $ linesToPara lns
blockToMan _ (RawBlock f str)
| f == Format "man" = return $ text str
| otherwise = return empty
@@ -367,4 +369,3 @@ inlineToMan _ (Note contents) = do
notes <- liftM stNotes get
let ref = show $ (length notes)
return $ char '[' <> text ref <> char ']'
-
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 3ad31d54a..471b28d39 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables #-}
+{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables, MultiWayIf #-}
{-
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
@@ -79,7 +79,7 @@ instance Default WriterEnv
, envRefShortcutable = True
, envBlockLevel = 0
}
-
+
data WriterState = WriterState { stNotes :: Notes
, stRefs :: Refs
, stIds :: Set.Set String
@@ -204,15 +204,10 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
_ -> blocks
else blocks
body <- blockListToMarkdown opts blocks'
- st <- get
- notes' <- notesToMarkdown opts (reverse $ stNotes st)
- st' <- get -- note that the notes may contain refs
- refs' <- refsToMarkdown opts (reverse $ stRefs st')
+ notesAndRefs' <- notesAndRefs opts
let render' :: Doc -> String
render' = render colwidth
- let main = render' $ body <>
- (if isEmpty notes' then empty else blankline <> notes') <>
- (if isEmpty refs' then empty else blankline <> refs')
+ let main = render' $ body <> notesAndRefs'
let context = defField "toc" (render' toc)
$ defField "body" main
$ (if isNullMeta meta
@@ -337,6 +332,23 @@ beginsWithOrderedListMarker str =
Left _ -> False
Right _ -> True
+notesAndRefs :: WriterOptions -> MD Doc
+notesAndRefs opts = do
+ notes' <- reverse <$> gets stNotes >>= notesToMarkdown opts
+ modify $ \s -> s { stNotes = [] }
+ refs' <- reverse <$> gets stRefs >>= refsToMarkdown opts
+ modify $ \s -> s { stRefs = [] }
+
+ let endSpacing =
+ if | writerReferenceLocation opts == EndOfDocument -> empty
+ | isEmpty notes' && isEmpty refs' -> empty
+ | otherwise -> blankline
+
+ return $
+ (if isEmpty notes' then empty else blankline <> notes') <>
+ (if isEmpty refs' then empty else blankline <> refs') <>
+ endSpacing
+
-- | Convert Pandoc block element to markdown.
blockToMarkdown :: WriterOptions -- ^ Options
-> Block -- ^ Block element
@@ -346,16 +358,7 @@ blockToMarkdown opts blk =
do doc <- blockToMarkdown' opts blk
blkLevel <- asks envBlockLevel
if writerReferenceLocation opts == EndOfBlock && blkLevel == 1
- then do st <- get
- notes' <- notesToMarkdown opts (reverse $ stNotes st)
- modify $ \s -> s { stNotes = [] }
- st' <- get -- note that the notes may contain refs
- refs' <- refsToMarkdown opts (reverse $ stRefs st')
- modify $ \s -> s { stRefs = [] }
- return $ doc <>
- (if isEmpty notes' then empty else blankline <> notes') <>
- (if isEmpty refs' then empty else blankline <> refs') <>
- (if (isEmpty notes' && isEmpty refs') then empty else blankline)
+ then notesAndRefs opts >>= (\d -> return $ doc <> d)
else return doc
blockToMarkdown' :: WriterOptions -- ^ Options
@@ -390,6 +393,12 @@ blockToMarkdown' opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) =
blockToMarkdown opts (Para [Image attr alt (src,tit)])
blockToMarkdown' opts (Para inlines) =
(<> blankline) `fmap` blockToMarkdown opts (Plain inlines)
+blockToMarkdown' opts (LineBlock lns) =
+ if isEnabled Ext_line_blocks opts
+ then do
+ mdLines <- mapM (inlineListToMarkdown opts) lns
+ return $ (vcat $ map (hang 2 (text "| ")) mdLines) <> blankline
+ else blockToMarkdown opts $ linesToPara lns
blockToMarkdown' opts (RawBlock f str)
| f == "markdown" = return $ text str <> text "\n"
| f == "html" && isEnabled Ext_raw_html opts = do
@@ -412,16 +421,7 @@ blockToMarkdown' opts (Header level attr inlines) = do
-- put them here.
blkLevel <- asks envBlockLevel
refs <- if writerReferenceLocation opts == EndOfSection && blkLevel == 1
- then do st <- get
- notes' <- notesToMarkdown opts (reverse $ stNotes st)
- modify $ \s -> s { stNotes = [] }
- st' <- get -- note that the notes may contain refs
- refs' <- refsToMarkdown opts (reverse $ stRefs st')
- modify $ \s -> s { stRefs = [] }
- return $
- (if isEmpty notes' then empty else blankline <> notes') <>
- (if isEmpty refs' then empty else blankline <> refs') <>
- (if (isEmpty notes' && isEmpty refs') then empty else blankline)
+ then notesAndRefs opts
else return empty
plain <- asks envPlain
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 0da8bc98c..3b2028997 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -120,6 +120,9 @@ blockToMediaWiki (Para inlines) = do
then "<p>" ++ contents ++ "</p>"
else contents ++ if null lev then "\n" else ""
+blockToMediaWiki (LineBlock lns) =
+ blockToMediaWiki $ linesToPara lns
+
blockToMediaWiki (RawBlock f str)
| f == Format "mediawiki" = return str
| f == Format "html" = return str
diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs
index fc96e3e3c..2a9bc5138 100644
--- a/src/Text/Pandoc/Writers/Native.hs
+++ b/src/Text/Pandoc/Writers/Native.hs
@@ -45,6 +45,8 @@ prettyList ds =
-- | Prettyprint Pandoc block element.
prettyBlock :: Block -> Doc
+prettyBlock (LineBlock lines') =
+ "LineBlock" $$ prettyList (map (text . show) lines')
prettyBlock (BlockQuote blocks) =
"BlockQuote" $$ prettyList (map prettyBlock blocks)
prettyBlock (OrderedList attribs blockLists) =
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index e0434c630..583aa2e4a 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -33,6 +33,7 @@ module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.XML
+import Text.Pandoc.Shared (linesToPara)
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Pretty
@@ -291,6 +292,7 @@ blockToOpenDocument o bs
| Para b <- bs = if null b
then return empty
else inParagraphTags =<< inlinesToOpenDocument o b
+ | LineBlock b <- bs = blockToOpenDocument o $ linesToPara b
| Div _ xs <- bs = blocksToOpenDocument o xs
| Header i _ b <- bs = setFirstPara >>
(inHeaderTags i =<< inlinesToOpenDocument o b)
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 96baacbb6..18a820f2e 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -164,6 +164,17 @@ blockToOrg (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
blockToOrg (Para inlines) = do
contents <- inlineListToOrg inlines
return $ contents <> blankline
+blockToOrg (LineBlock lns) = do
+ let splitStanza [] = []
+ splitStanza xs = case break (== mempty) xs of
+ (l, []) -> l : []
+ (l, _:r) -> l : splitStanza r
+ let joinWithLinefeeds = nowrap . mconcat . intersperse cr
+ let joinWithBlankLines = mconcat . intersperse blankline
+ let prettyfyStanza ls = joinWithLinefeeds <$> mapM inlineListToOrg ls
+ contents <- joinWithBlankLines <$> mapM prettyfyStanza (splitStanza lns)
+ return $ blankline $$ "#+BEGIN_VERSE" $$
+ nest 2 contents $$ "#+END_VERSE" <> blankline
blockToOrg (RawBlock "html" str) =
return $ blankline $$ "#+BEGIN_HTML" $$
nest 2 (text str) $$ "#+END_HTML" $$ blankline
@@ -362,7 +373,7 @@ inlineToOrg (Note contents) = do
notes <- get >>= (return . stNotes)
modify $ \st -> st { stNotes = contents:notes }
let ref = show $ (length notes) + 1
- return $ " [" <> text ref <> "]"
+ return $ "[" <> text ref <> "]"
orgPath :: String -> String
orgPath src =
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 98c39bdaf..21f1acd6e 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -201,11 +201,12 @@ blockToRST (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline
blockToRST (Para inlines)
| LineBreak `elem` inlines = do -- use line block if LineBreaks
- lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines
- return $ (vcat $ map (hang 2 (text "| ")) lns) <> blankline
+ linesToLineBlock $ splitBy (==LineBreak) inlines
| otherwise = do
contents <- inlineListToRST inlines
return $ contents <> blankline
+blockToRST (LineBlock lns) =
+ linesToLineBlock lns
blockToRST (RawBlock f@(Format f') str)
| f == "rst" = return $ text str
| otherwise = return $ blankline <> ".. raw:: " <>
@@ -328,6 +329,12 @@ definitionListItemToRST (label, defs) = do
tabstop <- get >>= (return . writerTabStop . stOptions)
return $ label' $$ nest tabstop (nestle contents <> cr)
+-- | Format a list of lines as line block.
+linesToLineBlock :: [[Inline]] -> State WriterState Doc
+linesToLineBlock inlineLines = do
+ lns <- mapM inlineListToRST inlineLines
+ return $ (vcat $ map (hang 2 (text "| ")) lns) <> blankline
+
-- | Convert list of Pandoc block elements to RST.
blockListToRST' :: Bool
-> [Block] -- ^ List of block elements
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 79a28c880..b87ef0fd3 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -233,6 +233,8 @@ blockToRTF indent alignment (Plain lst) =
rtfCompact indent 0 alignment $ inlineListToRTF lst
blockToRTF indent alignment (Para lst) =
rtfPar indent 0 alignment $ inlineListToRTF lst
+blockToRTF indent alignment (LineBlock lns) =
+ blockToRTF indent alignment $ linesToPara lns
blockToRTF indent alignment (BlockQuote lst) =
concatMap (blockToRTF (indent + indentIncrement) alignment) lst
blockToRTF indent _ (CodeBlock _ str) =
diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs
index b9e683ab9..018884202 100644
--- a/src/Text/Pandoc/Writers/TEI.hs
+++ b/src/Text/Pandoc/Writers/TEI.hs
@@ -108,7 +108,7 @@ plainToPara :: Block -> Block
plainToPara (Plain x) = Para x
plainToPara x = x
--- | Convert a list of pairs of terms and definitions into a TEI
+-- | Convert a list of pairs of terms and definitions into a TEI
-- list with labels and items.
deflistItemsToTEI :: WriterOptions -> [([Inline],[[Block]])] -> Doc
deflistItemsToTEI opts items =
@@ -167,6 +167,8 @@ blockToTEI opts (Plain lst) = blockToTEI opts $ Para lst
-- inTagsSimple "textobject" (inTagsSimple "phrase" alt))
blockToTEI opts (Para lst) =
inTags False "p" [] $ inlinesToTEI opts lst
+blockToTEI opts (LineBlock lns) =
+ blockToTEI opts $ linesToPara lns
blockToTEI opts (BlockQuote blocks) =
inTagsIndented "quote" $ blocksToTEI opts blocks
blockToTEI _ (CodeBlock (_,classes,_) str) =
@@ -174,7 +176,7 @@ blockToTEI _ (CodeBlock (_,classes,_) str) =
flush (text (escapeStringForXML str) <> cr <> text "</ab>")
where lang = if null langs
then ""
- else escapeStringForXML (head langs)
+ else escapeStringForXML (head langs)
isLang l = map toLower l `elem` map (map toLower) languages
langsFrom s = if isLang s
then [s]
@@ -210,7 +212,7 @@ blockToTEI _ HorizontalRule =
selfClosingTag "milestone" [("unit","undefined"), ("type","separator"),("rendition","line")]
-- | TEI Tables
--- TEI Simple's tables are composed of cells and rows; other
+-- TEI Simple's tables are composed of cells and rows; other
-- table info in the AST is here lossily discard.
blockToTEI opts (Table _ _ _ headers rows) =
let
@@ -219,8 +221,8 @@ blockToTEI opts (Table _ _ _ headers rows) =
-- then return empty
-- else tableRowToTEI opts headers
in
- inTags True "table" [] $
- vcat $ [headers'] <> map (tableRowToTEI opts) rows
+ inTags True "table" [] $
+ vcat $ [headers'] <> map (tableRowToTEI opts) rows
tableRowToTEI :: WriterOptions
-> [[Block]]
@@ -276,7 +278,7 @@ inlineToTEI _ (Math t str) =
text (str)
DisplayMath -> inTags True "figure" [("type","math")] $
inTags False "formula" [("notation","TeX")] $ text (str)
-
+
inlineToTEI _ (RawInline f x) | f == "tei" = text x
| otherwise = empty
inlineToTEI _ LineBreak = selfClosingTag "lb" []
@@ -317,4 +319,3 @@ idAndRole (id',cls,_) = ident ++ role
role = if null cls
then []
else [("role", unwords cls)]
-
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 8420704dc..b94229943 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -145,6 +145,9 @@ blockToTexinfo (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
blockToTexinfo (Para lst) =
inlineListToTexinfo lst -- this is handled differently from Plain in blockListToTexinfo
+blockToTexinfo (LineBlock lns) =
+ blockToTexinfo $ linesToPara lns
+
blockToTexinfo (BlockQuote lst) = do
contents <- blockListToTexinfo lst
return $ text "@quotation" $$
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 98f9157fb..ec70f3072 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -130,6 +130,9 @@ blockToTextile opts (Para inlines) = do
then "<p>" ++ contents ++ "</p>"
else contents ++ if null listLevel then "\n" else ""
+blockToTextile opts (LineBlock lns) =
+ blockToTextile opts $ linesToPara lns
+
blockToTextile _ (RawBlock f str)
| f == Format "html" || f == Format "textile" = return str
| otherwise = return ""
diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs
index 05563970a..8afbfef92 100644
--- a/src/Text/Pandoc/Writers/ZimWiki.hs
+++ b/src/Text/Pandoc/Writers/ZimWiki.hs
@@ -33,7 +33,8 @@ http://zim-wiki.org/manual/Help/Wiki_Syntax.html
module Text.Pandoc.Writers.ZimWiki ( writeZimWiki ) where
import Text.Pandoc.Definition
import Text.Pandoc.Options ( WriterOptions(writerTableOfContents, writerStandalone, writerTemplate, writerWrapText), WrapOption(..) )
-import Text.Pandoc.Shared ( escapeURI, removeFormatting, trimr, substitute )
+import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting, trimr
+ , substitute )
import Text.Pandoc.Writers.Shared ( defField, metaToJSON )
import Text.Pandoc.ImageSize
import Text.Pandoc.Templates ( renderTemplate' )
@@ -111,6 +112,9 @@ blockToZimWiki opts (Para inlines) = do
contents <- inlineListToZimWiki opts inlines
return $ contents ++ if null indent then "\n" else ""
+blockToZimWiki opts (LineBlock lns) = do
+ blockToZimWiki opts $ linesToPara lns
+
blockToZimWiki opts (RawBlock f str)
| f == Format "zimwiki" = return str
| f == Format "html" = do cont <- indentFromHTML opts str; return cont