aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/RST.hs34
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs16
2 files changed, 24 insertions, 26 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 7785861cc..54b6fa34a 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -113,15 +113,16 @@ titleTransform (bs, meta) =
metaFromDefList :: [([Inline], [[Block]])] -> Meta -> Meta
metaFromDefList ds meta = adjustAuthors $ foldr f meta ds
where f (k,v) = setMeta (map toLower $ stringify k) (mconcat $ map fromList v)
- adjustAuthors (Meta metamap) = Meta $ M.adjust toPlain "author"
+ adjustAuthors (Meta metamap) = Meta $ M.adjust splitAuthors "author"
$ M.adjust toPlain "date"
$ M.adjust toPlain "title"
- $ M.adjust splitAuthors "authors"
+ $ M.mapKeys (\k -> if k == "authors" then "author" else k)
$ metamap
toPlain (MetaBlocks [Para xs]) = MetaInlines xs
toPlain x = x
- splitAuthors (MetaBlocks [Para xs]) = MetaList $ map MetaInlines
- $ splitAuthors' xs
+ splitAuthors (MetaBlocks [Para xs])
+ = MetaList $ map MetaInlines
+ $ splitAuthors' xs
splitAuthors x = x
splitAuthors' = map normalizeSpaces .
splitOnSemi . concatMap factorSemi
@@ -185,22 +186,22 @@ block = choice [ codeBlock
-- field list
--
-rawFieldListItem :: String -> RSTParser (String, String)
-rawFieldListItem indent = try $ do
- string indent
+rawFieldListItem :: Int -> RSTParser (String, String)
+rawFieldListItem minIndent = try $ do
+ indent <- length <$> many (char ' ')
+ guard $ indent >= minIndent
char ':'
name <- many1Till (noneOf "\n") (char ':')
(() <$ lookAhead newline) <|> skipMany1 spaceChar
first <- anyLine
- rest <- option "" $ try $ do lookAhead (string indent >> spaceChar)
+ rest <- option "" $ try $ do lookAhead (count indent (char ' ') >> spaceChar)
indentedBlock
let raw = (if null first then "" else (first ++ "\n")) ++ rest ++ "\n"
return (name, raw)
-fieldListItem :: String
- -> RSTParser (Inlines, [Blocks])
-fieldListItem indent = try $ do
- (name, raw) <- rawFieldListItem indent
+fieldListItem :: Int -> RSTParser (Inlines, [Blocks])
+fieldListItem minIndent = try $ do
+ (name, raw) <- rawFieldListItem minIndent
let term = B.str name
contents <- parseFromString parseBlocks raw
optional blanklines
@@ -208,7 +209,7 @@ fieldListItem indent = try $ do
fieldList :: RSTParser Blocks
fieldList = try $ do
- indent <- lookAhead $ many spaceChar
+ indent <- length <$> lookAhead (many spaceChar)
items <- many1 $ fieldListItem indent
case items of
[] -> return mempty
@@ -521,11 +522,11 @@ directive' = do
skipMany spaceChar
top <- many $ satisfy (/='\n')
<|> try (char '\n' <*
- notFollowedBy' (rawFieldListItem " ") <*
+ notFollowedBy' (rawFieldListItem 3) <*
count 3 (char ' ') <*
notFollowedBy blankline)
newline
- fields <- many $ rawFieldListItem " "
+ fields <- many $ rawFieldListItem 3
body <- option "" $ try $ blanklines >> indentedBlock
optional blanklines
let body' = body ++ "\n\n"
@@ -576,6 +577,9 @@ directive' = do
role -> role })
"code" -> codeblock (lookup "number-lines" fields) (trim top) body
"code-block" -> codeblock (lookup "number-lines" fields) (trim top) body
+ "aafig" -> do
+ let attribs = ("", ["aafig"], map (\(k,v) -> (k, trimr v)) fields)
+ return $ B.codeBlockWith attribs $ stripTrailingNewlines body
"math" -> return $ B.para $ mconcat $ map B.displayMath
$ toChunks $ top ++ "\n\n" ++ body
"figure" -> do
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 3095cf508..cec420dcf 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -35,7 +35,7 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options
import Text.Pandoc.Walk (query)
import Text.Printf ( printf )
-import Data.List ( intercalate, isPrefixOf )
+import Data.List ( intercalate )
import Control.Monad.State
import Text.Pandoc.Pretty
import Text.Pandoc.Templates ( renderTemplate' )
@@ -283,14 +283,6 @@ inlineToConTeXt (RawInline "tex" str) = return $ text str
inlineToConTeXt (RawInline _ _) = return empty
inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr
inlineToConTeXt Space = return space
--- autolink
-inlineToConTeXt (Link [Str str] (src, tit))
- | if "mailto:" `isPrefixOf` src
- then src == escapeURI ("mailto:" ++ str)
- else src == escapeURI str =
- inlineToConTeXt (Link
- [RawInline "context" "\\hyphenatedurl{", Str str, RawInline "context" "}"]
- (src, tit))
-- Handle HTML-like internal document references to sections
inlineToConTeXt (Link txt (('#' : ref), _)) = do
opts <- gets stOptions
@@ -305,6 +297,7 @@ inlineToConTeXt (Link txt (('#' : ref), _)) = do
<> brackets (text ref)
inlineToConTeXt (Link txt (src, _)) = do
+ let isAutolink = txt == [Str src]
st <- get
let next = stNextRef st
put $ st {stNextRef = next + 1}
@@ -313,8 +306,9 @@ inlineToConTeXt (Link txt (src, _)) = do
return $ "\\useURL"
<> brackets (text ref)
<> brackets (text $ escapeStringUsing [('#',"\\#"),('%',"\\%")] src)
- <> brackets empty
- <> brackets label
+ <> (if isAutolink
+ then empty
+ else brackets empty <> brackets label)
<> "\\from"
<> brackets (text ref)
inlineToConTeXt (Image _ (src, _)) = do