diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/Org.hs | 28 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/ParserState.hs | 32 |
2 files changed, 57 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 610397d58..ffddd0fa6 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -122,6 +122,25 @@ addToNotesTable note = do updateState $ \s -> s{ orgStateNotes' = note:oldnotes } -- +-- Export Settings +-- +exportSetting :: OrgParser () +exportSetting = choice + [ booleanSetting "^" setExportSubSuperscripts + ] <?> "export setting" + +booleanSetting :: String -> ExportSettingSetter Bool -> OrgParser () +booleanSetting str setter = try $ do + string str + char ':' + value <- many nonspaceChar + let boolValue = case value of + "nil" -> False + "{}" -> False + _ -> True + updateState $ modifyExportSettings setter boolValue + +-- -- Parser -- parseOrg :: OrgParser Pandoc @@ -590,8 +609,9 @@ optionLine :: OrgParser () optionLine = try $ do key <- metaKey case key of - "link" -> parseLinkFormat >>= uncurry addLinkFormat - _ -> mzero + "link" -> parseLinkFormat >>= uncurry addLinkFormat + "options" -> () <$ sepBy spaces exportSetting + _ -> mzero parseLinkFormat :: OrgParser ((String, String -> String)) parseLinkFormat = try $ do @@ -1460,7 +1480,9 @@ subOrSuperExpr = try $ where enclosing (left, right) s = left : s ++ [right] simpleSubOrSuperString :: OrgParser String -simpleSubOrSuperString = try $ +simpleSubOrSuperString = try $ do + state <- getState + guard . exportSubSuperscripts . orgStateExportSettings $ state choice [ string "*" , mappend <$> option [] ((:[]) <$> oneOf "+-") <*> many1 alphaNum diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 680c469f3..49cfa2be2 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -38,6 +38,10 @@ module Text.Pandoc.Readers.Org.ParserState , trimInlinesF , runF , returnF + , ExportSettingSetter + , exportSubSuperscripts + , setExportSubSuperscripts + , modifyExportSettings ) where import Control.Monad (liftM, liftM2) @@ -70,6 +74,12 @@ type OrgBlockAttributes = M.Map String String -- link-type, the corresponding function transforms the given link string. type OrgLinkFormatters = M.Map String (String -> String) +-- | Export settings <http://orgmode.org/manual/Export-settings.html> +-- These settings can be changed via OPTIONS statements. +data ExportSettings = ExportSettings + { exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts + } + -- | Org-mode parser state data OrgParserState = OrgParserState { orgStateOptions :: ReaderOptions @@ -77,6 +87,7 @@ data OrgParserState = OrgParserState , orgStateBlockAttributes :: OrgBlockAttributes , orgStateEmphasisCharStack :: [Char] , orgStateEmphasisNewlines :: Maybe Int + , orgStateExportSettings :: ExportSettings , orgStateLastForbiddenCharPos :: Maybe SourcePos , orgStateLastPreCharPos :: Maybe SourcePos , orgStateLastStrPos :: Maybe SourcePos @@ -119,6 +130,8 @@ instance HasHeaderMap OrgParserState where extractHeaderMap = orgStateHeaderMap updateHeaderMap f s = s{ orgStateHeaderMap = f (orgStateHeaderMap s) } +instance Default ExportSettings where + def = defaultExportSettings instance Default OrgParserState where def = defaultOrgParserState @@ -130,6 +143,7 @@ defaultOrgParserState = OrgParserState , orgStateBlockAttributes = M.empty , orgStateEmphasisCharStack = [] , orgStateEmphasisNewlines = Nothing + , orgStateExportSettings = def , orgStateLastForbiddenCharPos = Nothing , orgStateLastPreCharPos = Nothing , orgStateLastStrPos = Nothing @@ -142,6 +156,24 @@ defaultOrgParserState = OrgParserState , orgStateHeaderMap = M.empty } +defaultExportSettings :: ExportSettings +defaultExportSettings = ExportSettings + { exportSubSuperscripts = True + } + + +-- +-- Setter for exporting options +-- +type ExportSettingSetter a = a -> ExportSettings -> ExportSettings + +setExportSubSuperscripts :: ExportSettingSetter Bool +setExportSubSuperscripts val es = es { exportSubSuperscripts = val } + +-- | Modify a parser state +modifyExportSettings :: ExportSettingSetter a -> a -> OrgParserState -> OrgParserState +modifyExportSettings setter val state = + state { orgStateExportSettings = setter val . orgStateExportSettings $ state } -- -- Parser state reader |