Skip to content

Commit

Permalink
Org reader: support macros
Browse files Browse the repository at this point in the history
Closes: #3401
  • Loading branch information
tarleb committed May 6, 2017
1 parent 9f0a804 commit da8c153
Show file tree
Hide file tree
Showing 5 changed files with 102 additions and 1 deletion.
21 changes: 21 additions & 0 deletions src/Text/Pandoc/Readers/Org/Inlines.hs
Original file line number Diff line number Diff line change
Expand Up @@ -120,6 +120,7 @@ inline =
, superscript
, inlineLaTeX
, exportSnippet
, macro
, smart
, symbol
] <* (guard =<< newlinesCountWithinLimits)
Expand Down Expand Up @@ -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
Expand Down
27 changes: 26 additions & 1 deletion src/Text/Pandoc/Readers/Org/Meta.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)

Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
18 changes: 18 additions & 0 deletions src/Text/Pandoc/Readers/Org/ParserState.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,9 @@ module Text.Pandoc.Readers.Org.ParserState
, TodoState (..)
, activeTodoMarkers
, registerTodoSequence
, MacroExpander
, lookupMacro
, registerMacro
, F
, askF
, asksF
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -156,6 +163,8 @@ defaultOrgParserState = OrgParserState
, orgStateLastPreCharPos = Nothing
, orgStateLastStrPos = Nothing
, orgStateLinkFormatters = M.empty
, orgStateMacros = M.empty
, orgStateMacroDepth = 0
, orgStateMeta = return nullMeta
, orgStateNotes' = []
, orgStateOptions = def
Expand Down Expand Up @@ -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
Expand Down
18 changes: 18 additions & 0 deletions test/Tests/Readers/Org.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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" $
Expand Down
19 changes: 19 additions & 0 deletions test/command/3401.md
Original file line number Diff line number Diff line change
@@ -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"]]
```

0 comments on commit da8c153

Please sign in to comment.