aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2017-05-06 10:59:40 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2017-05-06 11:00:32 +0200
commitda8c153a6872a040440f8853a37f559bb3b26b02 (patch)
tree704c0e00947092cdda83cd74f7e211b072619743
parent9f0a80457fb0ab343af651af8c7bc6f9dc467f55 (diff)
downloadpandoc-da8c153a6872a040440f8853a37f559bb3b26b02.tar.gz
Org reader: support macros
Closes: #3401
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs21
-rw-r--r--src/Text/Pandoc/Readers/Org/Meta.hs27
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs18
-rw-r--r--test/Tests/Readers/Org.hs18
-rw-r--r--test/command/3401.md19
5 files changed, 102 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index 64ffb8ef5..5772e4157 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -120,6 +120,7 @@ inline =
, superscript
, inlineLaTeX
, exportSnippet
+ , macro
, smart
, symbol
] <* (guard =<< newlinesCountWithinLimits)
@@ -839,6 +840,26 @@ 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
diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs
index 7938fc6c6..8c362f209 100644
--- a/src/Text/Pandoc/Readers/Org/Meta.hs
+++ b/src/Text/Pandoc/Readers/Org/Meta.hs
@@ -46,7 +46,7 @@ import Text.Pandoc.Definition
import Control.Monad (mzero, void)
import Data.Char (toLower)
-import Data.List (intersperse)
+import Data.List (intersperse, sort)
import qualified Data.Map as M
import Network.HTTP (urlEncode)
@@ -151,6 +151,7 @@ optionLine = try $ do
"todo" -> todoSequence >>= updateState . registerTodoSequence
"seq_todo" -> todoSequence >>= updateState . registerTodoSequence
"typ_todo" -> todoSequence >>= updateState . registerTodoSequence
+ "macro" -> macroDefinition >>= updateState . registerMacro
_ -> mzero
addLinkFormat :: Monad m => String
@@ -218,3 +219,27 @@ todoSequence = try $ do
let todoMarkers = map (TodoMarker Todo) todo
doneMarkers = map (TodoMarker Done) done
in todoMarkers ++ doneMarkers
+
+macroDefinition :: Monad m => OrgParser m (String, [String] -> String)
+macroDefinition = try $ do
+ macroName <- many1 nonspaceChar <* skipSpaces
+ firstPart <- expansionPart
+ (elemOrder, parts) <- unzip <$> many ((,) <$> placeholder <*> expansionPart)
+ let expander = mconcat . alternate (firstPart:parts) . reorder elemOrder
+ return (macroName, expander)
+ where
+ placeholder :: Monad m => OrgParser m Int
+ placeholder = try . fmap read $ char '$' *> many1 digit
+
+ expansionPart :: Monad m => OrgParser m String
+ expansionPart = try $ many (notFollowedBy placeholder *> noneOf "\n\r")
+
+ alternate :: [a] -> [a] -> [a]
+ alternate [] ys = ys
+ alternate xs [] = xs
+ alternate (x:xs) (y:ys) = x : y : alternate xs ys
+
+ reorder :: [Int] -> [String] -> [String]
+ reorder perm xs =
+ let element n = take 1 $ drop (n - 1) xs
+ in concatMap element perm
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
index bdd1dc951..e47565814 100644
--- a/src/Text/Pandoc/Readers/Org/ParserState.hs
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -39,6 +39,9 @@ module Text.Pandoc.Readers.Org.ParserState
, TodoState (..)
, activeTodoMarkers
, registerTodoSequence
+ , MacroExpander
+ , lookupMacro
+ , registerMacro
, F
, askF
, asksF
@@ -78,6 +81,8 @@ type OrgNoteTable = [OrgNoteRecord]
-- | Map of functions for link transformations. The map key is refers to the
-- link-type, the corresponding function transforms the given link string.
type OrgLinkFormatters = M.Map String (String -> String)
+-- | Macro expander function
+type MacroExpander = [String] -> String
-- | The states in which a todo item can be
data TodoState = Todo | Done
@@ -105,6 +110,8 @@ data OrgParserState = OrgParserState
, orgStateLastPreCharPos :: Maybe SourcePos
, orgStateLastStrPos :: Maybe SourcePos
, orgStateLinkFormatters :: OrgLinkFormatters
+ , orgStateMacros :: M.Map String MacroExpander
+ , orgStateMacroDepth :: Int
, orgStateMeta :: F Meta
, orgStateNotes' :: OrgNoteTable
, orgStateOptions :: ReaderOptions
@@ -156,6 +163,8 @@ defaultOrgParserState = OrgParserState
, orgStateLastPreCharPos = Nothing
, orgStateLastStrPos = Nothing
, orgStateLinkFormatters = M.empty
+ , orgStateMacros = M.empty
+ , orgStateMacroDepth = 0
, orgStateMeta = return nullMeta
, orgStateNotes' = []
, orgStateOptions = def
@@ -185,6 +194,15 @@ activeTodoSequences st =
activeTodoMarkers :: OrgParserState -> TodoSequence
activeTodoMarkers = concat . activeTodoSequences
+lookupMacro :: String -> OrgParserState -> Maybe MacroExpander
+lookupMacro macroName = M.lookup macroName . orgStateMacros
+
+registerMacro :: (String, MacroExpander) -> OrgParserState -> OrgParserState
+registerMacro (name, expander) st =
+ let curMacros = orgStateMacros st
+ in st{ orgStateMacros = M.insert name expander curMacros }
+
+
--
-- Export Settings
diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs
index 7a7960396..278d91cfd 100644
--- a/test/Tests/Readers/Org.hs
+++ b/test/Tests/Readers/Org.hs
@@ -469,6 +469,24 @@ tests =
, citationNoteNum = 0
, citationHash = 0}
in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}")
+
+ , "Macro" =:
+ unlines [ "#+MACRO: HELLO /Hello, $1/"
+ , "{{{HELLO(World)}}}"
+ ] =?>
+ para (emph "Hello, World")
+
+ , "Macro repeting its argument" =:
+ unlines [ "#+MACRO: HELLO $1$1"
+ , "{{{HELLO(moin)}}}"
+ ] =?>
+ para "moinmoin"
+
+ , "Macro called with too few arguments" =:
+ unlines [ "#+MACRO: HELLO Foo $1 $2 Bar"
+ , "{{{HELLO()}}}"
+ ] =?>
+ para "Foo Bar"
]
, testGroup "Meta Information" $
diff --git a/test/command/3401.md b/test/command/3401.md
new file mode 100644
index 000000000..99528553a
--- /dev/null
+++ b/test/command/3401.md
@@ -0,0 +1,19 @@
+See #3401 and <http://orgmode.org/manual/Macro-replacement.html>
+
+```
+% pandoc -f org -t native
+#+MACRO: HELLO /Hello, $1/
+{{{HELLO(World)}}}
+^D
+[Para [Emph [Str "Hello,",Space,Str "World"]]]
+```
+
+Inverted argument order
+
+```
+% pandoc -f org -t native
+#+MACRO: A $2,$1
+{{{A(1,2)}}}
+^D
+[Para [Str "2,1"]]
+```