aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs1
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs5
-rw-r--r--src/Text/Pandoc/Readers/Docx/Fonts.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs72
-rw-r--r--src/Text/Pandoc/Readers/Docx/Reducible.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/StyleMap.hs1
-rw-r--r--src/Text/Pandoc/Readers/Docx/Util.hs1
-rw-r--r--src/Text/Pandoc/Readers/EPUB.hs2
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs3
-rw-r--r--src/Text/Pandoc/Readers/Haddock.hs4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs25
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs19
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs2
-rw-r--r--src/Text/Pandoc/Readers/Native.hs1
-rw-r--r--src/Text/Pandoc/Readers/OPML.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Arrows/State.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs3
-rw-r--r--src/Text/Pandoc/Readers/Odt/ContentReader.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs3
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/Utils.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/Namespaces.hs1
-rw-r--r--src/Text/Pandoc/Readers/Odt/StyleReader.hs1
-rw-r--r--src/Text/Pandoc/Readers/Org.hs20
-rw-r--r--src/Text/Pandoc/Readers/RST.hs3
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs1
-rw-r--r--src/Text/Pandoc/Readers/TeXMath.hs1
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs3
-rw-r--r--src/Text/Pandoc/Readers/Txt2Tags.hs2
34 files changed, 104 insertions, 82 deletions
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index e6f8026ab..51a35c8ad 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -32,7 +32,6 @@ CommonMark is a strongly specified variant of Markdown: http://commonmark.org.
module Text.Pandoc.Readers.CommonMark (readCommonMark)
where
-import Prelude
import CMark
import Data.Text (unpack, pack)
import Data.List (groupBy)
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 0845f5e03..f679ddb57 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -1,5 +1,4 @@
module Text.Pandoc.Readers.DocBook ( readDocBook ) where
-import Prelude
import Data.Char (toUpper)
import Text.Pandoc.Shared (safeRead)
import Text.Pandoc.Options
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 35b2ba3fd..9f1c7af0a 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -74,7 +74,6 @@ module Text.Pandoc.Readers.Docx
( readDocx
) where
-import Prelude
import Codec.Archive.Zip
import Text.Pandoc.Definition
import Text.Pandoc.Options
@@ -504,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/Fonts.hs b/src/Text/Pandoc/Readers/Docx/Fonts.hs
index 967ca296c..b44c71412 100644
--- a/src/Text/Pandoc/Readers/Docx/Fonts.hs
+++ b/src/Text/Pandoc/Readers/Docx/Fonts.hs
@@ -29,7 +29,6 @@ Utilities to convert between font codepoints and unicode characters.
-}
module Text.Pandoc.Readers.Docx.Fonts (getUnicode, Font(..)) where
-import Prelude
-- | Enumeration of recognised fonts
data Font = Symbol -- ^ <http://en.wikipedia.org/wiki/Symbol_(typeface) Adobe Symbol>
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index 0c9297139..c265ad074 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -33,7 +33,6 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets
, listParagraphDivs
) where
-import Prelude
import Text.Pandoc.JSON
import Text.Pandoc.Generic (bottomUp)
import Text.Pandoc.Shared (trim)
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 91eab1339..5910a476b 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -50,7 +50,6 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, Cell(..)
, archiveToDocx
) where
-import Prelude
import Codec.Archive.Zip
import Text.XML.Light
import Data.Maybe
@@ -76,6 +75,7 @@ data ReaderEnv = ReaderEnv { envNotes :: Notes
, envFont :: Maybe Font
, envCharStyles :: CharStyleMap
, envParStyles :: ParStyleMap
+ , envLocation :: DocumentLocation
}
deriving Show
@@ -88,7 +88,7 @@ instance Error DocxError where
type D = ExceptT DocxError (Reader ReaderEnv)
runD :: D a -> ReaderEnv -> Either DocxError a
-runD dx re = runReader (runExceptT dx ) re
+runD dx re = runReader (runExceptT dx) re
maybeToD :: Maybe a -> D a
maybeToD (Just a) = return a
@@ -141,7 +141,10 @@ data AbstractNumb = AbstractNumb String [Level]
-- (ilvl, format, string, start)
type Level = (String, String, String, Maybe Integer)
-data Relationship = Relationship (RelId, Target)
+data DocumentLocation = InDocument | InFootnote | InEndnote
+ deriving (Eq,Show)
+
+data Relationship = Relationship DocumentLocation RelId Target
deriving Show
data Notes = Notes NameSpaces
@@ -175,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
@@ -239,7 +243,6 @@ defaultRunStyle = RunStyle { isBold = Nothing
, rUnderline = Nothing
, rStyle = Nothing}
-
type Target = String
type Anchor = String
type URL = String
@@ -256,7 +259,8 @@ archiveToDocx archive = do
rels = archiveToRelationships archive
media = archiveToMedia archive
(styles, parstyles) = archiveToStyles archive
- rEnv = ReaderEnv notes numbering rels media Nothing styles parstyles
+ rEnv =
+ ReaderEnv notes numbering rels media Nothing styles parstyles InDocument
doc <- runD (archiveToDocument archive) rEnv
return $ Docx doc
@@ -363,29 +367,30 @@ archiveToNotes zf =
in
Notes ns fn en
-filePathIsRel :: FilePath -> Bool
-filePathIsRel fp =
- let (dir, name) = splitFileName fp
- in
- (dir == "word/_rels/") && ((takeExtension name) == ".rels")
+filePathToRelType :: FilePath -> Maybe DocumentLocation
+filePathToRelType "word/_rels/document.xml.rels" = Just InDocument
+filePathToRelType "word/_rels/footnotes.xml.rels" = Just InFootnote
+filePathToRelType "word/_rels/endnotes.xml.rels" = Just InEndnote
+filePathToRelType _ = Nothing
-relElemToRelationship :: Element -> Maybe Relationship
-relElemToRelationship element | qName (elName element) == "Relationship" =
+relElemToRelationship :: DocumentLocation -> Element -> Maybe Relationship
+relElemToRelationship relType element | qName (elName element) == "Relationship" =
do
relId <- findAttr (QName "Id" Nothing Nothing) element
target <- findAttr (QName "Target" Nothing Nothing) element
- return $ Relationship (relId, target)
-relElemToRelationship _ = Nothing
-
-
+ return $ Relationship relType relId target
+relElemToRelationship _ _ = Nothing
+
+filePathToRelationships :: Archive -> FilePath -> [Relationship]
+filePathToRelationships ar fp | Just relType <- filePathToRelType fp
+ , Just entry <- findEntryByPath fp ar
+ , Just relElems <- (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry =
+ mapMaybe (relElemToRelationship relType) $ elChildren relElems
+filePathToRelationships _ _ = []
+
archiveToRelationships :: Archive -> [Relationship]
archiveToRelationships archive =
- let relPaths = filter filePathIsRel (filesInArchive archive)
- entries = mapMaybe (\f -> findEntryByPath f archive) relPaths
- relElems = mapMaybe (parseXMLDoc . UTF8.toStringLazy . fromEntry) entries
- rels = mapMaybe relElemToRelationship $ concatMap elChildren relElems
- in
- rels
+ concatMap (filePathToRelationships archive) $ filesInArchive archive
filePathIsMedia :: FilePath -> Bool
filePathIsMedia fp =
@@ -410,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" &&
@@ -561,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
@@ -574,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
@@ -597,13 +603,16 @@ elemToBodyPart ns element
return $ Tbl caption grid tblLook rows
elemToBodyPart _ _ = throwError WrongElem
-lookupRelationship :: RelId -> [Relationship] -> Maybe Target
-lookupRelationship relid rels =
- lookup relid (map (\(Relationship pair) -> pair) rels)
+lookupRelationship :: DocumentLocation -> RelId -> [Relationship] -> Maybe Target
+lookupRelationship docLocation relid rels =
+ lookup (docLocation, relid) pairs
+ where
+ pairs = map (\(Relationship loc relid' target) -> ((loc, relid'), target)) rels
expandDrawingId :: String -> D (FilePath, B.ByteString)
expandDrawingId s = do
- target <- asks (lookupRelationship s . envRelationships)
+ location <- asks envLocation
+ target <- asks (lookupRelationship location s . envRelationships)
case target of
Just filepath -> do
bytes <- asks (lookup ("word/" ++ filepath) . envMedia)
@@ -658,9 +667,10 @@ elemToParPart ns element
elemToParPart ns element
| isElem ns "w" "hyperlink" element
, Just relId <- findAttr (elemName ns "r" "id") element = do
+ location <- asks envLocation
runs <- mapD (elemToRun ns) (elChildren element)
rels <- asks envRelationships
- case lookupRelationship relId rels of
+ case lookupRelationship location relId rels of
Just target -> do
case findAttr (elemName ns "w" "anchor") element of
Just anchor -> return $ ExternalHyperLink (target ++ '#':anchor) runs
@@ -700,7 +710,7 @@ elemToRun ns element
, Just fnId <- findAttr (elemName ns "w" "id") ref = do
notes <- asks envNotes
case lookupFootnote fnId notes of
- Just e -> do bps <- mapD (elemToBodyPart ns) (elChildren e)
+ Just e -> do bps <- local (\r -> r {envLocation=InFootnote}) $ mapD (elemToBodyPart ns) (elChildren e)
return $ Footnote bps
Nothing -> return $ Footnote []
elemToRun ns element
@@ -709,7 +719,7 @@ elemToRun ns element
, Just enId <- findAttr (elemName ns "w" "id") ref = do
notes <- asks envNotes
case lookupEndnote enId notes of
- Just e -> do bps <- mapD (elemToBodyPart ns) (elChildren e)
+ Just e -> do bps <- local (\r -> r {envLocation=InEndnote}) $ mapD (elemToBodyPart ns) (elChildren e)
return $ Endnote bps
Nothing -> return $ Endnote []
elemToRun ns element
diff --git a/src/Text/Pandoc/Readers/Docx/Reducible.hs b/src/Text/Pandoc/Readers/Docx/Reducible.hs
index a850141f6..c93b40119 100644
--- a/src/Text/Pandoc/Readers/Docx/Reducible.hs
+++ b/src/Text/Pandoc/Readers/Docx/Reducible.hs
@@ -7,7 +7,6 @@ module Text.Pandoc.Readers.Docx.Reducible ( concatReduce
where
-import Prelude
import Text.Pandoc.Builder
import Data.List
import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr)
diff --git a/src/Text/Pandoc/Readers/Docx/StyleMap.hs b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
index 231653106..2901ea2a3 100644
--- a/src/Text/Pandoc/Readers/Docx/StyleMap.hs
+++ b/src/Text/Pandoc/Readers/Docx/StyleMap.hs
@@ -5,7 +5,6 @@ module Text.Pandoc.Readers.Docx.StyleMap ( StyleMaps(..)
, hasStyleName
) where
-import Prelude
import Text.XML.Light
import Text.Pandoc.Readers.Docx.Util
import Control.Monad.State
diff --git a/src/Text/Pandoc/Readers/Docx/Util.hs b/src/Text/Pandoc/Readers/Docx/Util.hs
index 2790c0d1a..891f107b0 100644
--- a/src/Text/Pandoc/Readers/Docx/Util.hs
+++ b/src/Text/Pandoc/Readers/Docx/Util.hs
@@ -5,7 +5,6 @@ module Text.Pandoc.Readers.Docx.Util (
, elemToNameSpaces
) where
-import Prelude
import Text.XML.Light
import Data.Maybe (mapMaybe)
diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs
index 9938bb70b..b8698fe26 100644
--- a/src/Text/Pandoc/Readers/EPUB.hs
+++ b/src/Text/Pandoc/Readers/EPUB.hs
@@ -8,7 +8,6 @@ module Text.Pandoc.Readers.EPUB
(readEPUB)
where
-import Prelude
import Text.XML.Light
import Text.Pandoc.Definition hiding (Attr)
import Text.Pandoc.Walk (walk, query)
@@ -17,6 +16,7 @@ import Text.Pandoc.Options ( ReaderOptions(..), readerTrace)
import Text.Pandoc.Shared (escapeURI, collapseFilePath, addMetaField)
import Text.Pandoc.MediaBag (MediaBag, insertMedia)
import Text.Pandoc.Compat.Except (MonadError, throwError, runExcept, Except)
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.MIME (MimeType)
import qualified Text.Pandoc.Builder as B
import Codec.Archive.Zip ( Archive (..), toArchive, fromEntry
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 570efc2be..ce10a289e 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -38,7 +38,6 @@ module Text.Pandoc.Readers.HTML ( readHtml
, isCommentTag
) where
-import Prelude
import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match
import Text.Pandoc.Definition
@@ -67,7 +66,7 @@ import Control.Monad.Reader (Reader,ask, asks, local, runReader)
import Network.URI (isURI)
import Text.Pandoc.Error
import Text.Pandoc.CSS (foldOrElse, pickStyleAttrProps)
-
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Parsec.Error
diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs
index 578a89d21..16f3d7ef3 100644
--- a/src/Text/Pandoc/Readers/Haddock.hs
+++ b/src/Text/Pandoc/Readers/Haddock.hs
@@ -14,9 +14,9 @@ module Text.Pandoc.Readers.Haddock
( readHaddock
) where
-import Prelude
import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.Shared (trim, splitBy)
import Data.List (intersperse, stripPrefix)
import Data.Maybe (fromMaybe)
@@ -130,7 +130,7 @@ makeExample prompt expression result =
<> (mconcat $ intersperse B.linebreak $ map coder result')
where
-- 1. drop trailing whitespace from the prompt, remember the prefix
- prefix = takeWhile (`elem` [' ','\t']) prompt
+ prefix = takeWhile (`elem` " \t") prompt
-- 2. drop, if possible, the exact same sequence of whitespace
-- characters from each result line
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index ffb4182ad..b9645d034 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -35,7 +35,6 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,
handleIncludes
) where
-import Prelude
import Text.Pandoc.Definition
import Text.Pandoc.Walk
import Text.Pandoc.Shared
@@ -170,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/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index d3b71c499..7e811a966 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -32,7 +32,6 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.
module Text.Pandoc.Readers.Markdown ( readMarkdown,
readMarkdownWithWarnings ) where
-import Prelude
import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate )
import qualified Data.Map as M
import Data.Scientific (coefficient, base10Exponent)
@@ -40,6 +39,7 @@ import Data.Ord ( comparing )
import Data.Char ( isSpace, isAlphaNum, toLower )
import Data.Maybe
import Text.Pandoc.Definition
+import Text.Pandoc.Emoji (emojis)
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.Yaml as Yaml
@@ -63,6 +63,7 @@ import Text.HTML.TagSoup.Match (tagOpen)
import qualified Data.Set as Set
import Text.Printf (printf)
import Debug.Trace (trace)
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.Error
type MarkdownParser = Parser [Char] ParserState
@@ -1467,6 +1468,7 @@ inline = choice [ whitespace
, exampleRef
, smart
, return . B.singleton <$> charRef
+ , emoji
, symbol
, ltSign
] <?> "inline"
@@ -1898,6 +1900,21 @@ rawHtmlInline = do
else not . isTextTag
return $ return $ B.rawInline "html" result
+-- Emoji
+
+emojiChars :: [Char]
+emojiChars = ['a'..'z'] ++ ['0'..'9'] ++ ['_','+','-']
+
+emoji :: MarkdownParser (F Inlines)
+emoji = try $ do
+ guardEnabled Ext_emoji
+ char ':'
+ emojikey <- many1 (oneOf emojiChars)
+ char ':'
+ case M.lookup emojikey emojis of
+ Just s -> return (return (B.str s))
+ Nothing -> mzero
+
-- Citations
cite :: MarkdownParser (F Inlines)
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index b21fb58c0..ffac51e7b 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -36,10 +36,10 @@ _ parse templates?
-}
module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where
-import Prelude
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.Options
import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isCommentTag )
import Text.Pandoc.XML ( fromEntities )
diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs
index 73ac0d4b2..4ec164e19 100644
--- a/src/Text/Pandoc/Readers/Native.hs
+++ b/src/Text/Pandoc/Readers/Native.hs
@@ -30,7 +30,6 @@ Conversion of a string representation of a pandoc type (@Pandoc@,
-}
module Text.Pandoc.Readers.Native ( readNative ) where
-import Prelude
import Text.Pandoc.Definition
import Text.Pandoc.Shared (safeRead)
diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs
index e7633e414..b2e5f2e67 100644
--- a/src/Text/Pandoc/Readers/OPML.hs
+++ b/src/Text/Pandoc/Readers/OPML.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
module Text.Pandoc.Readers.OPML ( readOPML ) where
-import Prelude
import Data.Char (toUpper)
import Text.Pandoc.Options
import Text.Pandoc.Definition
diff --git a/src/Text/Pandoc/Readers/Odt.hs b/src/Text/Pandoc/Readers/Odt.hs
index cc15c9e20..a925c1d84 100644
--- a/src/Text/Pandoc/Readers/Odt.hs
+++ b/src/Text/Pandoc/Readers/Odt.hs
@@ -32,7 +32,6 @@ Entry point to the odt reader.
module Text.Pandoc.Readers.Odt ( readOdt ) where
-import Prelude
import Codec.Archive.Zip
import qualified Text.XML.Light as XML
diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs
index 2cc83183f..30f96c557 100644
--- a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs
+++ b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs
@@ -46,6 +46,7 @@ import Control.Monad
import Data.Foldable
+import Text.Pandoc.Compat.Monoid
import Text.Pandoc.Readers.Odt.Arrows.Utils
import Text.Pandoc.Readers.Odt.Generic.Fallible
diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
index e7d2bcb92..8c9ee0539 100644
--- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
@@ -39,7 +39,6 @@ with an equivalent return value.
-- We export everything
module Text.Pandoc.Readers.Odt.Arrows.Utils where
-import Prelude
import Control.Arrow
import Control.Monad ( join, MonadPlus(..) )
@@ -47,7 +46,7 @@ import qualified Data.Foldable as F
import Text.Pandoc.Readers.Odt.Generic.Fallible
import Text.Pandoc.Readers.Odt.Generic.Utils
-
+import Text.Pandoc.Compat.Monoid
and2 :: (Arrow a) => a b c -> a b c' -> a b (c,c')
and2 = (&&&)
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 06dd83668..1f1c57646 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -39,7 +39,6 @@ module Text.Pandoc.Readers.Odt.ContentReader
, read_body
) where
-import Prelude
import Control.Arrow
import Control.Applicative hiding ( liftA, liftA2, liftA3 )
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
index 7213bc8f1..d0fdc228f 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs
@@ -39,10 +39,9 @@ compatible instances of "ArrowChoice".
-- We export everything
module Text.Pandoc.Readers.Odt.Generic.Fallible where
-import Prelude
import Control.Applicative
import Control.Monad
-
+import Text.Pandoc.Compat.Monoid ((<>))
import qualified Data.Foldable as F
-- | Default for now. Will probably become a class at some point.
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs
index 0a6095e98..82ae3e20e 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs
@@ -31,7 +31,6 @@ typesafe Haskell namespace identifiers and unsafe "real world" namespaces.
module Text.Pandoc.Readers.Odt.Generic.Namespaces where
-import Prelude
import qualified Data.Map as M
--
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs
index b7a555219..afd7d616c 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs
@@ -30,7 +30,6 @@ A map of values to sets of values.
module Text.Pandoc.Readers.Odt.Generic.SetMap where
-import Prelude
import qualified Data.Map as M
import qualified Data.Set as S
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
index a09b4cc1d..6c10ed61d 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs
@@ -53,7 +53,6 @@ module Text.Pandoc.Readers.Odt.Generic.Utils
, composition
) where
-import Prelude
import Control.Category ( Category, (>>>), (<<<) )
import qualified Control.Category as Cat ( id )
import Control.Monad ( msum )
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
index 7d72ee125..8c03d1a09 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
@@ -116,7 +116,6 @@ module Text.Pandoc.Readers.Odt.Generic.XMLConverter
, matchContent
) where
-import Prelude
import Control.Applicative hiding ( liftA, liftA2 )
import Control.Monad ( MonadPlus )
import Control.Arrow
diff --git a/src/Text/Pandoc/Readers/Odt/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Namespaces.hs
index f00093368..deb009998 100644
--- a/src/Text/Pandoc/Readers/Odt/Namespaces.hs
+++ b/src/Text/Pandoc/Readers/Odt/Namespaces.hs
@@ -31,7 +31,6 @@ Namespaces used in odt files.
module Text.Pandoc.Readers.Odt.Namespaces ( Namespace (..)
) where
-import Prelude
import Data.List ( isPrefixOf )
import Data.Maybe ( fromMaybe, listToMaybe )
import qualified Data.Map as M ( empty, insert )
diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
index 4140bf2c7..96cfed0b3 100644
--- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
@@ -70,7 +70,6 @@ module Text.Pandoc.Readers.Odt.StyleReader
, readStylesAt
) where
-import Prelude
import Control.Arrow
import Control.Applicative hiding ( liftA, liftA2, liftA3 )
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 6e14febeb..3be47cfd4 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Readers.Org
- Copyright : Copyright (C) 2014 Albert Krewinkel
+ Copyright : Copyright (C) 2014-2015 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -30,11 +30,11 @@ Conversion of org-mode formatted plain text to 'Pandoc' document.
-}
module Text.Pandoc.Readers.Org ( readOrg ) where
-import Prelude
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Builder ( Inlines, Blocks, HasMeta(..),
trimInlines )
import Text.Pandoc.Definition
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.Options
import qualified Text.Pandoc.Parsing as P
import Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF
@@ -994,13 +994,16 @@ definitionListItem :: OrgParser Int
-> OrgParser (F (Inlines, [Blocks]))
definitionListItem parseMarkerGetLength = try $ do
markerLength <- parseMarkerGetLength
- term <- manyTill (noneOf "\n\r") (try $ string "::")
+ term <- manyTill (noneOf "\n\r") (try definitionMarker)
line1 <- anyLineNewline
blank <- option "" ("\n" <$ blankline)
cont <- concat <$> many (listContinuation markerLength)
term' <- parseFromString parseInlines term
contents' <- parseFromString parseBlocks $ line1 ++ blank ++ cont
return $ (,) <$> term' <*> fmap (:[]) contents'
+ where
+ definitionMarker =
+ spaceChar *> string "::" <* (spaceChar <|> lookAhead P.newline)
-- parse raw text for one list item, excluding start marker and continuations
@@ -1585,8 +1588,11 @@ smart :: OrgParser (F Inlines)
smart = do
getOption readerSmart >>= guard
doubleQuoted <|> singleQuoted <|>
- choice (map (return <$>) [orgApostrophe, dash, ellipses])
- where orgApostrophe =
+ choice (map (return <$>) [orgApostrophe, orgDash, orgEllipses])
+ where
+ orgDash = dash <* updatePositions '-'
+ orgEllipses = ellipses <* updatePositions '.'
+ orgApostrophe =
(char '\'' <|> char '\8217') <* updateLastPreCharPos
<* updateLastForbiddenCharPos
*> return (B.str "\x2019")
@@ -1594,9 +1600,10 @@ smart = do
singleQuoted :: OrgParser (F Inlines)
singleQuoted = try $ do
singleQuoteStart
+ updatePositions '\''
withQuoteContext InSingleQuote $
fmap B.singleQuoted . trimInlinesF . mconcat <$>
- many1Till inline singleQuoteEnd
+ many1Till inline (singleQuoteEnd <* updatePositions '\'')
-- doubleQuoted will handle regular double-quoted sections, as well
-- as dialogues with an open double-quote without a close double-quote
@@ -1604,6 +1611,7 @@ singleQuoted = try $ do
doubleQuoted :: OrgParser (F Inlines)
doubleQuoted = try $ do
doubleQuoteStart
+ updatePositions '"'
contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline)
(withQuoteContext InDoubleQuote $ (doubleQuoteEnd <* updateLastForbiddenCharPos) >> return
(fmap B.doubleQuoted . trimInlinesF $ contents))
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 82fa67407..199e7f3f8 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -33,7 +33,6 @@ module Text.Pandoc.Readers.RST (
readRST,
readRSTWithWarnings
) where
-import Prelude
import Text.Pandoc.Definition
import Text.Pandoc.Builder (setMeta, fromList)
import Text.Pandoc.Shared
@@ -49,7 +48,7 @@ import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
import qualified Text.Pandoc.Builder as B
import Data.Sequence (viewr, ViewR(..))
import Data.Char (toLower, isHexDigit, isSpace)
-
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.Error
-- | Parse reStructuredText string and return Pandoc document.
diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs
index 558e9691a..fc2bdc069 100644
--- a/src/Text/Pandoc/Readers/TWiki.hs
+++ b/src/Text/Pandoc/Readers/TWiki.hs
@@ -33,7 +33,6 @@ module Text.Pandoc.Readers.TWiki ( readTWiki
, readTWikiWithWarnings
) where
-import Prelude
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Options
diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs
index ad0eacb2b..e5778b123 100644
--- a/src/Text/Pandoc/Readers/TeXMath.hs
+++ b/src/Text/Pandoc/Readers/TeXMath.hs
@@ -29,7 +29,6 @@ Conversion of TeX math to a list of 'Pandoc' inline elements.
-}
module Text.Pandoc.Readers.TeXMath ( texMathToInlines ) where
-import Prelude
import Text.Pandoc.Definition
import Text.TeXMath
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index a99831a56..3db01faf4 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -51,7 +51,6 @@ TODO : refactor common patterns across readers :
module Text.Pandoc.Readers.Textile ( readTextile) where
-import Prelude
import Text.Pandoc.Definition
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
import qualified Text.Pandoc.Builder as B
@@ -65,6 +64,7 @@ import Text.HTML.TagSoup.Match
import Data.List ( intercalate )
import Data.Char ( digitToInt, isUpper)
import Control.Monad ( guard, liftM, when )
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Printf
import Debug.Trace (trace)
import Text.Pandoc.Error
@@ -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/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs
index 3a3172734..58841f2ce 100644
--- a/src/Text/Pandoc/Readers/Txt2Tags.hs
+++ b/src/Text/Pandoc/Readers/Txt2Tags.hs
@@ -32,9 +32,9 @@ module Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags
, readTxt2TagsNoMacros)
where
-import Prelude
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines )
+import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Shared (escapeURI,compactify', compactify'DL)