{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Org.BlockStarts
( exampleLineStart
, hline
, noteMarker
, tableStart
, drawerStart
, headerStart
, metaLineStart
, latexEnvStart
, commentLineStart
, bulletListStart
, orderedListStart
, endOfBlock
) where
import Control.Monad (void)
import Data.Text (Text)
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Definition as Pandoc
import Text.Pandoc.Shared (safeRead)
import Text.Pandoc.Parsing (lowerAlpha, upperAlpha)
import Text.Pandoc.Extensions
import Data.Functor (($>))
hline :: Monad m => OrgParser m ()
hline :: forall (m :: * -> *). Monad m => OrgParser m ()
hline = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"-----"
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-')
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
() -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
headerStart :: Monad m => OrgParser m Int
= ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b. (a -> b) -> a -> b
$
([Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Char] -> Int)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*')) ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ') ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
tableStart :: Monad m => OrgParser m Char
tableStart :: forall (m :: * -> *). Monad m => OrgParser m Char
tableStart = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|'
gridTableStart :: Monad m => OrgParser m ()
gridTableStart :: forall (m :: * -> *). Monad m => OrgParser m ()
gridTableStart = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'+' ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-'
latexEnvStart :: Monad m => OrgParser m Text
latexEnvStart :: forall (m :: * -> *). Monad m => OrgParser m Text
latexEnvStart = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"\\begin{"
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
latexEnvName
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"}"
where
latexEnvName :: Monad m => OrgParser m Text
latexEnvName :: forall (m :: * -> *). Monad m => OrgParser m Text
latexEnvName = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend (Text -> Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) (a -> b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" (Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
"*")
listCounterCookie :: Monad m => OrgParser m Int
listCounterCookie :: forall (m :: * -> *). Monad m => OrgParser m Int
listCounterCookie = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b. (a -> b) -> a -> b
$
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"[@"
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall {u}. ParsecT Sources u (ReaderT OrgParserLocal m) Int
parseNum
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']'
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
eol)
where parseNum :: ParsecT Sources u (ReaderT OrgParserLocal m) Int
parseNum = (Text -> ParsecT Sources u (ReaderT OrgParserLocal m) Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> ParsecT Sources u (ReaderT OrgParserLocal m) Int)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Text
-> ParsecT Sources u (ReaderT OrgParserLocal m) Int
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit)
ParsecT Sources u (ReaderT OrgParserLocal m) Int
-> ParsecT Sources u (ReaderT OrgParserLocal m) Int
-> ParsecT Sources u (ReaderT OrgParserLocal m) Int
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ListNumberStyle, Int) -> Int
forall a b. (a, b) -> b
snd ((ListNumberStyle, Int) -> Int)
-> ParsecT
Sources u (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources u (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (ListNumberStyle, Int)
lowerAlpha ParsecT Sources u (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
-> ParsecT
Sources u (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
-> ParsecT
Sources u (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (ListNumberStyle, Int)
upperAlpha)
bulletListStart :: Monad m => OrgParser m Int
bulletListStart :: forall (m :: * -> *). Monad m => OrgParser m Int
bulletListStart = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a b. (a -> b) -> a -> b
$ do
Int
ind <- [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Char] -> Int)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf (if Int
ind Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then [Char]
"+-" else [Char]
"*+-")
OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
skipSpaces1 OrgParser m () -> OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m () -> OrgParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
eol
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe Int)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
listCounterCookie
Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
ind Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
eol :: Monad m => OrgParser m ()
eol :: forall (m :: * -> *). Monad m => OrgParser m ()
eol = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n')
orderedListStart :: Monad m => OrgParser m (Int, ListAttributes)
orderedListStart :: forall (m :: * -> *). Monad m => OrgParser m (Int, ListAttributes)
orderedListStart = ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes))
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
forall a b. (a -> b) -> a -> b
$ do
Int
ind <- [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Char] -> Int)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Bool
fancy <- Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall a b. (a -> b) -> a -> b
$ Bool
True Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fancy_lists
let styles :: [ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle]
styles = (ParsecT Sources st (ReaderT OrgParserLocal m) Char
-> ParsecT Sources st (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources st (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit ParsecT Sources st (ReaderT OrgParserLocal m) Text
-> ListNumberStyle
-> ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> (if Bool
fancy
then ListNumberStyle
Decimal
else ListNumberStyle
DefaultStyle))
ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle
-> [ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle]
-> [ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle]
forall a. a -> [a] -> [a]
: if Bool
fancy
then [ (ListNumberStyle, Int) -> ListNumberStyle
forall a b. (a, b) -> a
fst ((ListNumberStyle, Int) -> ListNumberStyle)
-> ParsecT
Sources st (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
-> ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources st (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (ListNumberStyle, Int)
lowerAlpha
, (ListNumberStyle, Int) -> ListNumberStyle
forall a b. (a, b) -> a
fst ((ListNumberStyle, Int) -> ListNumberStyle)
-> ParsecT
Sources st (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
-> ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources st (ReaderT OrgParserLocal m) (ListNumberStyle, Int)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (ListNumberStyle, Int)
upperAlpha ]
else []
let delims :: [ParsecT Sources u (ReaderT OrgParserLocal m) ListNumberDelim]
delims = [ Char -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'.' ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ListNumberDelim
-> ParsecT Sources u (ReaderT OrgParserLocal m) ListNumberDelim
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> (if Bool
fancy
then ListNumberDelim
Period
else ListNumberDelim
DefaultDelim)
, Char -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
')' ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ListNumberDelim
-> ParsecT Sources u (ReaderT OrgParserLocal m) ListNumberDelim
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> (if Bool
fancy
then ListNumberDelim
OneParen
else ListNumberDelim
DefaultDelim)
]
ListNumberStyle
style <- [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ListNumberStyle]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ListNumberStyle
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ListNumberStyle]
forall {st}.
[ParsecT Sources st (ReaderT OrgParserLocal m) ListNumberStyle]
styles
ListNumberDelim
delim <- [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ListNumberDelim]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ListNumberDelim
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ListNumberDelim]
forall {u}.
[ParsecT Sources u (ReaderT OrgParserLocal m) ListNumberDelim]
delims
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
skipSpaces1 ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
eol
Int
start <- Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Int
1 ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
listCounterCookie
(Int, ListAttributes)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
ind Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, (Int
start, ListNumberStyle
style, ListNumberDelim
delim))
drawerStart :: Monad m => OrgParser m Text
drawerStart :: forall (m :: * -> *). Monad m => OrgParser m Text
drawerStart = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall {u}. ParsecT Sources u (ReaderT OrgParserLocal m) Text
drawerName ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
where drawerName :: ParsecT Sources u (ReaderT OrgParserLocal m) Text
drawerName = Char -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':' ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Text
-> ParsecT Sources u (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources u (ReaderT OrgParserLocal m) a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar (Char -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':')
metaLineStart :: Monad m => OrgParser m ()
metaLineStart :: forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"#+"
commentLineStart :: Monad m => OrgParser m ()
= ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"#" ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
" \n")
exampleLineStart :: Monad m => OrgParser m ()
exampleLineStart :: forall (m :: * -> *). Monad m => OrgParser m ()
exampleLineStart = () ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':' ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ') ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
eol))
noteMarker :: Monad m => OrgParser m Text
noteMarker :: forall (m :: * -> *). Monad m => OrgParser m Text
noteMarker = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ do
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'['
[ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']')
, Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) (Text -> Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
"fn:"
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) (a -> b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"\n\r\t ") (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']')
]
endOfBlock :: Monad m => OrgParser m ()
endOfBlock :: forall (m :: * -> *). Monad m => OrgParser m ()
endOfBlock = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
anyBlockStart
where
anyBlockStart :: Monad m => OrgParser m ()
anyBlockStart :: forall (m :: * -> *). Monad m => OrgParser m ()
anyBlockStart = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ([ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> [ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> [ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$
[ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
exampleLineStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
hline
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
commentLineStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
gridTableStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
noteMarker
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
tableStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
drawerStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
headerStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
latexEnvStart
, ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
bulletListStart
, ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Int, ListAttributes)
forall (m :: * -> *). Monad m => OrgParser m (Int, ListAttributes)
orderedListStart
]