aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Options.hs21
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs4
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs10
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs24
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs1
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs4
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs6
-rw-r--r--src/Text/Pandoc/Writers/Haddock.hs4
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs4
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs3
10 files changed, 46 insertions, 35 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index b7d268a65..158303acd 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
{-
Copyright (C) 2012-2015 John MacFarlane <jgm@berkeley.edu>
@@ -54,6 +54,7 @@ import Text.Pandoc.Highlighting (Style, pygments)
import Text.Pandoc.MediaBag (MediaBag)
import Data.Data (Data)
import Data.Typeable (Typeable)
+import GHC.Generics (Generic)
-- | Individually selectable syntax extensions.
data Extension =
@@ -114,7 +115,7 @@ data Extension =
| Ext_line_blocks -- ^ RST style line blocks
| Ext_epub_html_exts -- ^ Recognise the EPUB extended version of HTML
| Ext_shortcut_reference_links -- ^ Shortcut reference links
- deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable)
+ deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable, Generic)
pandocExtensions :: Set Extension
pandocExtensions = Set.fromList
@@ -258,7 +259,7 @@ data ReaderOptions = ReaderOptions{
, readerDefaultImageExtension :: String -- ^ Default extension for images
, readerTrace :: Bool -- ^ Print debugging info
, readerTrackChanges :: TrackChanges
-} deriving (Show, Read, Data, Typeable)
+} deriving (Show, Read, Data, Typeable, Generic)
instance Default ReaderOptions
where def = ReaderOptions{
@@ -280,7 +281,7 @@ instance Default ReaderOptions
-- Writer options
--
-data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable)
+data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Generic)
data HTMLMathMethod = PlainMath
| LaTeXMathML (Maybe String) -- url of LaTeXMathML.js
@@ -290,18 +291,18 @@ data HTMLMathMethod = PlainMath
| MathML (Maybe String) -- url of MathMLinHTML.js
| MathJax String -- url of MathJax.js
| KaTeX String String -- url of stylesheet and katex.js
- deriving (Show, Read, Eq, Data, Typeable)
+ deriving (Show, Read, Eq, Data, Typeable, Generic)
data CiteMethod = Citeproc -- use citeproc to render them
| Natbib -- output natbib cite commands
| Biblatex -- output biblatex cite commands
- deriving (Show, Read, Eq, Data, Typeable)
+ deriving (Show, Read, Eq, Data, Typeable, Generic)
-- | Methods for obfuscating email addresses in HTML.
data ObfuscationMethod = NoObfuscation
| ReferenceObfuscation
| JavascriptObfuscation
- deriving (Show, Read, Eq, Data, Typeable)
+ deriving (Show, Read, Eq, Data, Typeable, Generic)
-- | Varieties of HTML slide shows.
data HTMLSlideVariant = S5Slides
@@ -310,13 +311,13 @@ data HTMLSlideVariant = S5Slides
| DZSlides
| RevealJsSlides
| NoSlides
- deriving (Show, Read, Eq, Data, Typeable)
+ deriving (Show, Read, Eq, Data, Typeable, Generic)
-- | Options for accepting or rejecting MS Word track-changes.
data TrackChanges = AcceptChanges
| RejectChanges
| AllChanges
- deriving (Show, Read, Eq, Data, Typeable)
+ deriving (Show, Read, Eq, Data, Typeable, Generic)
-- | Options for writers
data WriterOptions = WriterOptions
@@ -363,7 +364,7 @@ data WriterOptions = WriterOptions
, writerMediaBag :: MediaBag -- ^ Media collected by docx or epub reader
, writerVerbose :: Bool -- ^ Verbose debugging output
, writerLaTeXArgs :: [String] -- ^ Flags to pass to latex-engine
- } deriving (Show, Data, Typeable)
+ } deriving (Show, Data, Typeable, Generic)
instance Default WriterOptions where
def = WriterOptions { writerStandalone = False
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index ab49bf002..9f1c7af0a 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -503,6 +503,10 @@ bodyPartToBlocks (ListItem pPr numId lvl levelInfo parparts) = do
]
blks <- bodyPartToBlocks (Paragraph pPr parparts)
return $ divWith ("", ["list-item"], kvs) blks
+bodyPartToBlocks (DummyListItem pPr _ parparts) =
+ let pPr' = pPr {pStyle = "ListParagraph": (pStyle pPr)}
+ in
+ bodyPartToBlocks $ Paragraph pPr' parparts
bodyPartToBlocks (Tbl _ _ _ []) =
return $ para mempty
bodyPartToBlocks (Tbl cap _ look (r:rs)) = do
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 02397d658..5910a476b 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -144,9 +144,6 @@ type Level = (String, String, String, Maybe Integer)
data DocumentLocation = InDocument | InFootnote | InEndnote
deriving (Eq,Show)
--- data RelationshipType = DocumentRel | FootnoteRel | EndnoteRel
--- deriving Show
-
data Relationship = Relationship DocumentLocation RelId Target
deriving Show
@@ -181,6 +178,7 @@ defaultParagraphStyle = ParagraphStyle { pStyle = []
data BodyPart = Paragraph ParagraphStyle [ParPart]
| ListItem ParagraphStyle String String Level [ParPart]
+ | DummyListItem ParagraphStyle String [ParPart]
| Tbl String TblGrid TblLook [Row]
| OMathPara [Exp]
deriving Show
@@ -245,7 +243,6 @@ defaultRunStyle = RunStyle { isBold = Nothing
, rUnderline = Nothing
, rStyle = Nothing}
-
type Target = String
type Anchor = String
type URL = String
@@ -418,6 +415,7 @@ lookupLevel numId ilvl (Numbering _ numbs absNumbs) = do
lvl <- lookup ilvl $ map (\l@(i, _, _, _) -> (i, l)) lvls
return lvl
+
numElemToNum :: NameSpaces -> Element -> Maybe Numb
numElemToNum ns element |
qName (elName element) == "num" &&
@@ -569,7 +567,7 @@ elemToBodyPart ns element
num <- asks envNumbering
case lookupLevel numId lvl num of
Just levelInfo -> return $ ListItem parstyle numId lvl levelInfo parparts
- Nothing -> throwError WrongElem
+ Nothing -> return $ DummyListItem parstyle lvl parparts
elemToBodyPart ns element
| isElem ns "w" "p" element = do
sty <- asks envParStyles
@@ -582,7 +580,7 @@ elemToBodyPart ns element
Just levelInfo ->
return $ ListItem parstyle numId lvl levelInfo parparts
Nothing ->
- throwError WrongElem
+ return $ DummyListItem parstyle lvl parparts
Nothing -> return $ Paragraph parstyle parparts
elemToBodyPart ns element
| isElem ns "w" "tbl" element = do
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index a6db6ffad..b9645d034 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -169,17 +169,23 @@ quoted' f starter ender = do
try ((f . mconcat) <$> manyTill inline ender) <|> lit startchs
doubleQuote :: LP Inlines
-doubleQuote =
- quoted' doubleQuoted (try $ string "``") (void $ try $ string "''")
- <|> quoted' doubleQuoted (string "“") (void $ char '”')
- -- the following is used by babel for localized quotes:
- <|> quoted' doubleQuoted (try $ string "\"`") (void $ try $ string "\"'")
- <|> quoted' doubleQuoted (string "\"") (void $ char '"')
+doubleQuote = do
+ smart <- getOption readerSmart
+ if smart
+ then quoted' doubleQuoted (try $ string "``") (void $ try $ string "''")
+ <|> quoted' doubleQuoted (string "“") (void $ char '”')
+ -- the following is used by babel for localized quotes:
+ <|> quoted' doubleQuoted (try $ string "\"`") (void $ try $ string "\"'")
+ <|> quoted' doubleQuoted (string "\"") (void $ char '"')
+ else str <$> many1 (oneOf "`'“”\"")
singleQuote :: LP Inlines
-singleQuote =
- quoted' singleQuoted (string "`") (try $ char '\'' >> notFollowedBy letter)
- <|> quoted' singleQuoted (string "‘") (try $ char '’' >> notFollowedBy letter)
+singleQuote = do
+ smart <- getOption readerSmart
+ if smart
+ then quoted' singleQuoted (string "`") (try $ char '\'' >> notFollowedBy letter)
+ <|> quoted' singleQuoted (string "‘") (try $ char '’' >> notFollowedBy letter)
+ else str <$> many1 (oneOf "`\'‘’")
inline :: LP Inlines
inline = (mempty <$ comment)
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index b1bf463af..3db01faf4 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -535,6 +535,7 @@ link = try $ do
image :: Parser [Char] ParserState Inlines
image = try $ do
char '!' >> notFollowedBy space
+ _ <- attributes -- ignore for now, until we have image attributes
src <- manyTill anyChar' (lookAhead $ oneOf "!(")
alt <- option "" (try $ (char '(' >> manyTill anyChar' (char ')')))
char '!'
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 40dbd839c..94c9ff28e 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -1070,8 +1070,8 @@ inlineToOpenXML opts (Note bs) = do
[ mknode "w:rPr" [] footnoteStyle
, mknode "w:footnoteRef" [] () ]
let notemarkerXml = RawInline (Format "openxml") $ ppElement notemarker
- let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : ils) : xs
- insertNoteRef (Para ils : xs) = Para (notemarkerXml : ils) : xs
+ let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : Space : ils) : xs
+ insertNoteRef (Para ils : xs) = Para (notemarkerXml : Space : ils) : xs
insertNoteRef xs = Para [notemarkerXml] : xs
oldListLevel <- gets stListLevel
oldParaProperties <- gets stParaProperties
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 9fdeb2c11..626732ef2 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -193,9 +193,6 @@ pandocToHtml opts (Pandoc meta blocks) = do
defField "revealjs-url" ("reveal.js" :: String) $
defField "s5-url" ("s5/default" :: String) $
defField "html5" (writerHtml5 opts) $
- defField "center" (case lookupMeta "center" meta of
- Just (MetaBool False) -> False
- _ -> True) $
metadata
return (thebody, context)
@@ -542,6 +539,9 @@ blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
let attribs = (if startnum /= 1
then [A.start $ toValue startnum]
else []) ++
+ (if numstyle == Example
+ then [A.class_ "example"]
+ else []) ++
(if numstyle /= DefaultStyle
then if writerHtml5 opts
then [A.type_ $
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index 14f398da9..5df6786ac 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -327,8 +327,8 @@ inlineToHaddock _ (RawInline f str)
inlineToHaddock _ (LineBreak) = return cr
inlineToHaddock _ Space = return space
inlineToHaddock opts (Cite _ lst) = inlineListToHaddock opts lst
-inlineToHaddock opts (Link txt (src, _)) = do
- linktext <- inlineListToHaddock opts txt
+inlineToHaddock _opts (Link txt (src, _)) = do
+ let linktext = text $ escapeString $ stringify txt
let useAuto = isURI src &&
case txt of
[Str s] | escapeURI s == src -> True
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index ae068a94f..95ea0c643 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -16,6 +16,7 @@ into InDesign with File -> Place.
module Text.Pandoc.Writers.ICML (writeICML) where
import Text.Pandoc.Definition
import Text.Pandoc.XML
+import Text.Pandoc.Readers.TeXMath (texMathToInlines)
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Shared (splitBy)
import Text.Pandoc.Options
@@ -410,7 +411,8 @@ inlineToICML opts style (Cite _ lst) = inlinesToICML opts style lst
inlineToICML _ style (Code _ str) = charStyle (codeName:style) $ text $ escapeStringForXML str
inlineToICML _ style Space = charStyle style space
inlineToICML _ style LineBreak = charStyle style $ text lineSeparator
-inlineToICML _ style (Math _ str) = charStyle style $ text $ escapeStringForXML str --InDesign doesn't really do math
+inlineToICML opts style (Math mt str) =
+ cat <$> mapM (inlineToICML opts style) (texMathToInlines mt str)
inlineToICML _ _ (RawInline f str)
| f == Format "icml" = return $ text str
| otherwise = return empty
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index ebe678dc0..7ee87f4af 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -191,8 +191,7 @@ writeOpenDocument opts (Pandoc meta blocks) =
listStyle (n,l) = inTags True "text:list-style"
[("style:name", "L" ++ show n)] (vcat l)
listStyles = map listStyle (stListStyles s)
- automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
- reverse $ styles ++ listStyles
+ automaticStyles = vcat $ reverse $ styles ++ listStyles
context = defField "body" body
$ defField "automatic-styles" (render' automaticStyles)
$ metadata