aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org/Parsing.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2016-05-22 16:52:06 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2016-05-25 22:54:45 +0200
commit39e8b4276e6d88d5cbb943d04c866dde9bf6473c (patch)
treef20d8b1e508c39524fe7084c50172861df4afad4 /src/Text/Pandoc/Readers/Org/Parsing.hs
parenta340c7249f8e19d36ee4a68663b4c97e0893292b (diff)
downloadpandoc-39e8b4276e6d88d5cbb943d04c866dde9bf6473c.tar.gz
Org reader: extract inline parser to module
Inline parsing code is moved to a separate module. Parsers for block starts are extracted as well, as those are used in the `endline` parser. This is part of the Org-mode reader cleanup effort.
Diffstat (limited to 'src/Text/Pandoc/Readers/Org/Parsing.hs')
-rw-r--r--src/Text/Pandoc/Readers/Org/Parsing.hs19
1 files changed, 19 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Parsing.hs b/src/Text/Pandoc/Readers/Org/Parsing.hs
index efe2ae25f..9a1420645 100644
--- a/src/Text/Pandoc/Readers/Org/Parsing.hs
+++ b/src/Text/Pandoc/Readers/Org/Parsing.hs
@@ -34,10 +34,14 @@ module Text.Pandoc.Readers.Org.Parsing
, blanklines
, newline
, parseFromString
+ , skipSpaces1
, inList
, withContext
, updateLastForbiddenCharPos
, updateLastPreCharPos
+ , orgArgKey
+ , orgArgWord
+ , orgArgWordChar
-- * Re-exports from Text.Pandoc.Parser
, ParserContext (..)
, many1Till
@@ -133,6 +137,10 @@ parseFromString parser str' = do
updateState $ \s -> s{ orgStateLastPreCharPos = oldLastPreCharPos }
return result
+-- | Skip one or more tab or space characters.
+skipSpaces1 :: OrgParser ()
+skipSpaces1 = skipMany1 spaceChar
+
-- | Like @Text.Parsec.Char.newline@, but causes additional state changes.
newline :: OrgParser Char
newline =
@@ -180,3 +188,14 @@ updateLastForbiddenCharPos = getPosition >>= \p ->
updateLastPreCharPos :: OrgParser ()
updateLastPreCharPos = getPosition >>= \p ->
updateState $ \s -> s{ orgStateLastPreCharPos = Just p}
+
+orgArgKey :: OrgParser String
+orgArgKey = try $
+ skipSpaces *> char ':'
+ *> many1 orgArgWordChar
+
+orgArgWord :: OrgParser String
+orgArgWord = many1 orgArgWordChar
+
+orgArgWordChar :: OrgParser Char
+orgArgWordChar = alphaNum <|> oneOf "-_"