aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org/Inlines.hs
diff options
context:
space:
mode:
authorschrieveslaach <schrieveslaach@online.de>2017-06-12 15:52:29 +0200
committerGitHub <noreply@github.com>2017-06-12 15:52:29 +0200
commit635f299b441e238ccd34e3ad61c5e36f0ca30067 (patch)
tree11cfc34402975bad208f9a48d075fe2ace959e70 /src/Text/Pandoc/Readers/Org/Inlines.hs
parent181c56d4003aa83abed23b95a452c4890aa3797c (diff)
parent23f3c2d7b4796d1af742a74999ce67924bf2abb3 (diff)
downloadpandoc-635f299b441e238ccd34e3ad61c5e36f0ca30067.tar.gz
Merge branch 'master' into textcolor-support
Diffstat (limited to 'src/Text/Pandoc/Readers/Org/Inlines.hs')
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs129
1 files changed, 82 insertions, 47 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index 64ffb8ef5..66273e05d 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-
-Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
@@ -18,8 +18,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
- Module : Text.Pandoc.Readers.Org.Options
- Copyright : Copyright (C) 2014-2016 Albert Krewinkel
+ Module : Text.Pandoc.Readers.Org.Inlines
+ Copyright : Copyright (C) 2014-2017 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -48,7 +48,7 @@ import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
import Text.TeXMath (DisplayType (..), readTeX, writePandoc)
import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
-import Control.Monad (guard, mplus, mzero, void, when)
+import Control.Monad (guard, mplus, mzero, unless, void, when)
import Control.Monad.Trans (lift)
import Data.Char (isAlphaNum, isSpace)
import Data.List (intersperse)
@@ -63,7 +63,7 @@ import Prelude hiding (sequence)
--
recordAnchorId :: PandocMonad m => String -> OrgParser m ()
recordAnchorId i = updateState $ \s ->
- s{ orgStateAnchorIds = i : (orgStateAnchorIds s) }
+ s{ orgStateAnchorIds = i : orgStateAnchorIds s }
pushToInlineCharStack :: PandocMonad m => Char -> OrgParser m ()
pushToInlineCharStack c = updateState $ \s ->
@@ -120,6 +120,7 @@ inline =
, superscript
, inlineLaTeX
, exportSnippet
+ , macro
, smart
, symbol
] <* (guard =<< newlinesCountWithinLimits)
@@ -183,7 +184,7 @@ cite = try $ berkeleyCite <|> do
, orgRefCite
, berkeleyTextualCite
]
- return $ (flip B.cite (B.text raw)) <$> cs
+ return $ flip B.cite (B.text raw) <$> cs
-- | A citation in Pandoc Org-mode style (@[prefix \@citekey suffix]@).
pandocOrgCite :: PandocMonad m => OrgParser m (F [Citation])
@@ -208,7 +209,7 @@ normalOrgRefCite = try $ do
orgRefCiteList :: PandocMonad m => CitationMode -> OrgParser m (F Citation)
orgRefCiteList citeMode = try $ do
key <- orgRefCiteKey
- returnF $ Citation
+ returnF Citation
{ citationId = key
, citationPrefix = mempty
, citationSuffix = mempty
@@ -231,11 +232,11 @@ berkeleyCite = try $ do
return $
if parens
then toCite
- . maybe id (\p -> alterFirst (prependPrefix p)) prefix
- . maybe id (\s -> alterLast (appendSuffix s)) suffix
+ . maybe id (alterFirst . prependPrefix) prefix
+ . maybe id (alterLast . appendSuffix) suffix
$ citationList
else maybe mempty (<> " ") prefix
- <> (toListOfCites $ map toInTextMode citationList)
+ <> toListOfCites (map toInTextMode citationList)
<> maybe mempty (", " <>) suffix
where
toCite :: [Citation] -> Inlines
@@ -249,7 +250,7 @@ berkeleyCite = try $ do
alterFirst, alterLast :: (a -> a) -> [a] -> [a]
alterFirst _ [] = []
- alterFirst f (c:cs) = (f c):cs
+ alterFirst f (c:cs) = f c : cs
alterLast f = reverse . alterFirst f . reverse
prependPrefix, appendSuffix :: Inlines -> Citation -> Citation
@@ -270,7 +271,7 @@ berkeleyCitationList = try $ do
skipSpaces
commonPrefix <- optionMaybe (try $ citationListPart <* char ';')
citations <- citeList
- commonSuffix <- optionMaybe (try $ citationListPart)
+ commonSuffix <- optionMaybe (try citationListPart)
char ']'
return (BerkeleyCitationList parens
<$> sequence commonPrefix
@@ -338,8 +339,15 @@ linkLikeOrgRefCite = try $ do
-- | Read a citation key. The characters allowed in citation keys are taken
-- from the `org-ref-cite-re` variable in `org-ref.el`.
orgRefCiteKey :: PandocMonad m => OrgParser m String
-orgRefCiteKey = try . many1 . satisfy $ \c ->
- isAlphaNum c || c `elem` ("-_:\\./"::String)
+orgRefCiteKey =
+ let citeKeySpecialChars = "-_:\\./," :: String
+ isCiteKeySpecialChar c = c `elem` citeKeySpecialChars
+ isCiteKeyChar c = isAlphaNum c || isCiteKeySpecialChar c
+ endOfCitation = try $ do
+ many $ satisfy isCiteKeySpecialChar
+ satisfy $ not . isCiteKeyChar
+ in try $ satisfy isCiteKeyChar `many1Till` lookAhead endOfCitation
+
-- | Supported citation types. Only a small subset of org-ref types is
-- supported for now. TODO: rewrite this, use LaTeX reader as template.
@@ -365,15 +373,16 @@ citation = try $ do
return $ do
x <- pref
y <- suff
- return $ Citation{ citationId = key
- , citationPrefix = B.toList x
- , citationSuffix = B.toList y
- , citationMode = if suppress_author
- then SuppressAuthor
- else NormalCitation
- , citationNoteNum = 0
- , citationHash = 0
- }
+ return Citation
+ { citationId = key
+ , citationPrefix = B.toList x
+ , citationSuffix = B.toList y
+ , citationMode = if suppress_author
+ then SuppressAuthor
+ else NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
where
prefix = trimInlinesF . mconcat <$>
manyTill inline (char ']' <|> (']' <$ lookAhead citeKey))
@@ -395,7 +404,7 @@ inlineNote = try $ do
ref <- many alphaNum
char ':'
note <- fmap B.para . trimInlinesF . mconcat <$> many1Till inline (char ']')
- when (not $ null ref) $
+ unless (null ref) $
addToNotesTable ("fn:" ++ ref, note)
return $ B.note <$> note
@@ -405,7 +414,7 @@ referencedNote = try $ do
return $ do
notes <- asksF orgStateNotes'
case lookup ref notes of
- Nothing -> return $ B.str $ "[" ++ ref ++ "]"
+ Nothing -> return . B.str $ "[" ++ ref ++ "]"
Just contents -> do
st <- askF
let contents' = runF contents st{ orgStateNotes' = [] }
@@ -429,7 +438,7 @@ explicitOrImageLink = try $ do
src <- srcF
case cleanLinkString title of
Just imgSrc | isImageFilename imgSrc ->
- pure $ B.link src "" $ B.image imgSrc mempty mempty
+ pure . B.link src "" $ B.image imgSrc mempty mempty
_ ->
linkToInlinesF src =<< title'
@@ -686,13 +695,13 @@ mathEnd c = try $ do
return res
-enclosedInlines :: PandocMonad m => OrgParser m a
+enclosedInlines :: (PandocMonad m, Show b) => OrgParser m a
-> OrgParser m b
-> OrgParser m (F Inlines)
enclosedInlines start end = try $
trimInlinesF . mconcat <$> enclosed start end inline
-enclosedRaw :: PandocMonad m => OrgParser m a
+enclosedRaw :: (PandocMonad m, Show b) => OrgParser m a
-> OrgParser m b
-> OrgParser m String
enclosedRaw start end = try $
@@ -771,7 +780,7 @@ notAfterForbiddenBorderChar = do
-- | Read a sub- or superscript expression
subOrSuperExpr :: PandocMonad m => OrgParser m (F Inlines)
subOrSuperExpr = try $
- choice [ id <$> charsInBalanced '{' '}' (noneOf "\n\r")
+ choice [ charsInBalanced '{' '}' (noneOf "\n\r")
, enclosing ('(', ')') <$> charsInBalanced '(' ')' (noneOf "\n\r")
, simpleSubOrSuperString
] >>= parseFromString (mconcat <$> many inline)
@@ -809,7 +818,7 @@ inlineLaTeX = try $ do
enableExtension Ext_raw_tex (readerExtensions def) } }
texMathToPandoc :: String -> Maybe [Inline]
- texMathToPandoc cs = (maybeRight $ readTeX cs) >>= writePandoc DisplayInline
+ texMathToPandoc cs = maybeRight (readTeX cs) >>= writePandoc DisplayInline
maybeRight :: Either a b -> Maybe b
maybeRight = either (const Nothing) Just
@@ -839,26 +848,49 @@ exportSnippet = try $ do
snippet <- manyTill anyChar (try $ string "@@")
returnF $ B.rawInline format snippet
+macro :: PandocMonad m => OrgParser m (F Inlines)
+macro = try $ do
+ recursionDepth <- orgStateMacroDepth <$> getState
+ guard $ recursionDepth < 15
+ string "{{{"
+ name <- many alphaNum
+ args <- ([] <$ string "}}}")
+ <|> char '(' *> argument `sepBy` char ',' <* eoa
+ expander <- lookupMacro name <$> getState
+ case expander of
+ Nothing -> mzero
+ Just fn -> do
+ updateState $ \s -> s { orgStateMacroDepth = recursionDepth + 1 }
+ res <- parseFromString (mconcat <$> many inline) $ fn args
+ updateState $ \s -> s { orgStateMacroDepth = recursionDepth }
+ return res
+ where
+ argument = many $ notFollowedBy eoa *> noneOf ","
+ eoa = string ")}}}"
+
smart :: PandocMonad m => OrgParser m (F Inlines)
-smart = do
- guardEnabled Ext_smart
- doubleQuoted <|> singleQuoted <|>
- choice (map (return <$>) [orgApostrophe, orgDash, orgEllipses])
+smart = choice [doubleQuoted, singleQuoted, orgApostrophe, orgDash, orgEllipses]
where
orgDash = do
- guard =<< getExportSetting exportSpecialStrings
- dash <* updatePositions '-'
+ guardOrSmartEnabled =<< getExportSetting exportSpecialStrings
+ pure <$> dash <* updatePositions '-'
orgEllipses = do
- guard =<< getExportSetting exportSpecialStrings
- ellipses <* updatePositions '.'
- orgApostrophe =
- (char '\'' <|> char '\8217') <* updateLastPreCharPos
- <* updateLastForbiddenCharPos
- *> return (B.str "\x2019")
+ guardOrSmartEnabled =<< getExportSetting exportSpecialStrings
+ pure <$> ellipses <* updatePositions '.'
+ orgApostrophe = do
+ guardEnabled Ext_smart
+ (char '\'' <|> char '\8217') <* updateLastPreCharPos
+ <* updateLastForbiddenCharPos
+ returnF (B.str "\x2019")
+
+guardOrSmartEnabled :: PandocMonad m => Bool -> OrgParser m ()
+guardOrSmartEnabled b = do
+ smartExtension <- extensionEnabled Ext_smart <$> getOption readerExtensions
+ guard (b || smartExtension)
singleQuoted :: PandocMonad m => OrgParser m (F Inlines)
singleQuoted = try $ do
- guard =<< getExportSetting exportSmartQuotes
+ guardOrSmartEnabled =<< getExportSetting exportSmartQuotes
singleQuoteStart
updatePositions '\''
withQuoteContext InSingleQuote $
@@ -870,10 +902,13 @@ singleQuoted = try $ do
-- in the same paragraph.
doubleQuoted :: PandocMonad m => OrgParser m (F Inlines)
doubleQuoted = try $ do
- guard =<< getExportSetting exportSmartQuotes
+ guardOrSmartEnabled =<< getExportSetting exportSmartQuotes
doubleQuoteStart
updatePositions '"'
contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline)
- (withQuoteContext InDoubleQuote $ (doubleQuoteEnd <* updateLastForbiddenCharPos) >> return
- (fmap B.doubleQuoted . trimInlinesF $ contents))
- <|> (return $ return (B.str "\8220") <> contents)
+ let doubleQuotedContent = withQuoteContext InDoubleQuote $ do
+ doubleQuoteEnd
+ updateLastForbiddenCharPos
+ return . fmap B.doubleQuoted . trimInlinesF $ contents
+ let leftQuoteAndContent = return $ pure (B.str "\8220") <> contents
+ doubleQuotedContent <|> leftQuoteAndContent