{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Org.Meta
( metaExport
, metaKey
, metaLine
) where
import Text.Pandoc.Readers.Org.BlockStarts
import Text.Pandoc.Readers.Org.ExportSettings (exportSettings)
import Text.Pandoc.Readers.Org.Inlines
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Shared (blocksToInlines, safeRead)
import Control.Monad (mzero, void)
import Data.List (intercalate, intersperse)
import Data.Map (Map)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Network.HTTP (urlEncode)
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Text as T
metaExport :: Monad m => OrgParser m (F Meta)
metaExport :: OrgParser m (F Meta)
metaExport = do
OrgParserState
st <- ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let settings :: ExportSettings
settings = OrgParserState -> ExportSettings
orgStateExportSettings OrgParserState
st
F Meta -> OrgParser m (F Meta)
forall (m :: * -> *) a. Monad m => a -> m a
return (F Meta -> OrgParser m (F Meta)) -> F Meta -> OrgParser m (F Meta)
forall a b. (a -> b) -> a -> b
$ (if ExportSettings -> Bool
exportWithAuthor ExportSettings
settings then Meta -> Meta
forall a. a -> a
id else Text -> Meta -> Meta
removeMeta Text
"author")
(Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if ExportSettings -> Bool
exportWithCreator ExportSettings
settings then Meta -> Meta
forall a. a -> a
id else Text -> Meta -> Meta
removeMeta Text
"creator")
(Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if ExportSettings -> Bool
exportWithEmail ExportSettings
settings then Meta -> Meta
forall a. a -> a
id else Text -> Meta -> Meta
removeMeta Text
"email")
(Meta -> Meta) -> F Meta -> F Meta
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParserState -> F Meta
orgStateMeta OrgParserState
st
removeMeta :: Text -> Meta -> Meta
removeMeta :: Text -> Meta -> Meta
removeMeta Text
key Meta
meta' =
let metaMap :: Map Text MetaValue
metaMap = Meta -> Map Text MetaValue
unMeta Meta
meta'
in Map Text MetaValue -> Meta
Meta (Map Text MetaValue -> Meta) -> Map Text MetaValue -> Meta
forall a b. (a -> b) -> a -> b
$ Text -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => k -> Map k a -> Map k a
Map.delete Text
key Map Text MetaValue
metaMap
metaLine :: PandocMonad m => OrgParser m Blocks
metaLine :: OrgParser m Blocks
metaLine = OrgParser m Blocks -> OrgParser m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Blocks -> OrgParser m Blocks)
-> OrgParser m Blocks -> OrgParser m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
metaLineStart OrgParser m Blocks
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
keywordLine
keywordLine :: PandocMonad m => OrgParser m ()
keywordLine :: OrgParser m ()
keywordLine = OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m () -> OrgParser m ())
-> OrgParser m () -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ do
Text
key <- Text -> Text
T.toLower (Text -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
metaKey
case Text -> Map Text (OrgParser m ()) -> Maybe (OrgParser m ())
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
key Map Text (OrgParser m ())
forall (m :: * -> *). PandocMonad m => Map Text (OrgParser m ())
keywordHandlers of
Maybe (OrgParser m ())
Nothing -> String -> OrgParser m ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> OrgParser m ()) -> String -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown keyword: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
key
Just OrgParser m ()
hd -> OrgParser m ()
hd
metaKey :: Monad m => OrgParser m Text
metaKey :: OrgParser m Text
metaKey = Text -> Text
T.toLower (Text -> Text) -> OrgParser m Text -> OrgParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char (String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
": \n\r")
OrgParser m Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':'
OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
infix 0 ~~>
(~~>) :: a -> b -> (a, b)
a
a ~~> :: a -> b -> (a, b)
~~> b
b = (a
a, b
b)
keywordHandlers :: PandocMonad m => Map Text (OrgParser m ())
keywordHandlers :: Map Text (OrgParser m ())
keywordHandlers = [(Text, OrgParser m ())] -> Map Text (OrgParser m ())
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[ Text
"author" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"author"
, Text
"creator" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> (Text -> Future OrgParserState Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Future OrgParserState Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
-> (Text -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Text -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
"creator"
, Text
"date" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
"date"
, Text
"description" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"description"
, Text
"email" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> (Text -> Future OrgParserState Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Future OrgParserState Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
-> (Text -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Text -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
"email"
, Text
"exclude_tags" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m [Tag]
forall (m :: * -> *). Monad m => OrgParser m [Tag]
tagList OrgParser m [Tag] -> ([Tag] -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> ([Tag] -> OrgParserState -> OrgParserState)
-> [Tag]
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tag] -> OrgParserState -> OrgParserState
setExcludedTags
, Text
"header-includes" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~>
OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"header-includes"
, Text
"html_head" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~>
Text -> OrgParser m (F Inlines)
forall (m :: * -> *). Monad m => Text -> OrgParser m (F Inlines)
metaExportSnippet Text
"html" OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectAsList Text
"header-includes"
, Text
"html_head_extra" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~>
Text -> OrgParser m (F Inlines)
forall (m :: * -> *). Monad m => Text -> OrgParser m (F Inlines)
metaExportSnippet Text
"html" OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectAsList Text
"header-includes"
, Text
"institute" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"institute"
, Text
"keywords" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"keywords"
, Text
"language" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> (Text -> Future OrgParserState Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Future OrgParserState Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
-> (Text -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Text -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
"lang"
, Text
"latex_class" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> (Text -> Future OrgParserState Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Future OrgParserState Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
-> (Text -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Text -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
"documentclass"
, Text
"latex_class_options" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~>
(Text -> Future OrgParserState Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Future OrgParserState Text)
-> (Text -> Text) -> Text -> Future OrgParserState Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.filter (Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (String
"[]" :: String)) (Text -> Future OrgParserState Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine)
ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Text)
-> (Text -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Text -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
"classoption"
, Text
"latex_header" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~>
Text -> OrgParser m (F Inlines)
forall (m :: * -> *). Monad m => Text -> OrgParser m (F Inlines)
metaExportSnippet Text
"latex" OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectAsList Text
"header-includes"
, Text
"latex_header_extra" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~>
Text -> OrgParser m (F Inlines)
forall (m :: * -> *). Monad m => Text -> OrgParser m (F Inlines)
metaExportSnippet Text
"latex" OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectAsList Text
"header-includes"
, Text
"link" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
addLinkFormatter
, Text
"macro" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (Text, [Text] -> Text)
forall (m :: * -> *). Monad m => OrgParser m (Text, [Text] -> Text)
macroDefinition OrgParser m (Text, [Text] -> Text)
-> ((Text, [Text] -> Text) -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> ((Text, [Text] -> Text) -> OrgParserState -> OrgParserState)
-> (Text, [Text] -> Text)
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, [Text] -> Text) -> OrgParserState -> OrgParserState
registerMacro
, Text
"nocite" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"nocite"
, Text
"options" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
exportSettings
, Text
"pandoc-emphasis-post" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (Maybe String)
forall (m :: * -> *). Monad m => OrgParser m (Maybe String)
emphChars OrgParser m (Maybe String)
-> (Maybe String -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> (Maybe String -> OrgParserState -> OrgParserState)
-> Maybe String
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe String -> OrgParserState -> OrgParserState
setEmphasisPostChar
, Text
"pandoc-emphasis-pre" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (Maybe String)
forall (m :: * -> *). Monad m => OrgParser m (Maybe String)
emphChars OrgParser m (Maybe String)
-> (Maybe String -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> (Maybe String -> OrgParserState -> OrgParserState)
-> Maybe String
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe String -> OrgParserState -> OrgParserState
setEmphasisPreChar
, Text
"result" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
, Text
"select_tags" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m [Tag]
forall (m :: * -> *). Monad m => OrgParser m [Tag]
tagList OrgParser m [Tag] -> ([Tag] -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> ([Tag] -> OrgParserState -> OrgParserState)
-> [Tag]
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tag] -> OrgParserState -> OrgParserState
setSelectedTags
, Text
"seq_todo" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m TodoSequence
forall (m :: * -> *). Monad m => OrgParser m TodoSequence
todoSequence OrgParser m TodoSequence
-> (TodoSequence -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> (TodoSequence -> OrgParserState -> OrgParserState)
-> TodoSequence
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TodoSequence -> OrgParserState -> OrgParserState
registerTodoSequence
, Text
"subtitle" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"subtitle"
, Text
"title" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
lineOfInlines OrgParser m (F Inlines)
-> (Inlines -> Meta -> Meta) -> OrgParser m ()
forall (m :: * -> *) a.
PandocMonad m =>
OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
`parseThen` Text -> Inlines -> Meta -> Meta
collectLines Text
"title"
, Text
"todo" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m TodoSequence
forall (m :: * -> *). Monad m => OrgParser m TodoSequence
todoSequence OrgParser m TodoSequence
-> (TodoSequence -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> (TodoSequence -> OrgParserState -> OrgParserState)
-> TodoSequence
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TodoSequence -> OrgParserState -> OrgParserState
registerTodoSequence
, Text
"typ_todo" Text -> OrgParser m () -> (Text, OrgParser m ())
forall a b. a -> b -> (a, b)
~~> OrgParser m TodoSequence
forall (m :: * -> *). Monad m => OrgParser m TodoSequence
todoSequence OrgParser m TodoSequence
-> (TodoSequence -> OrgParser m ()) -> OrgParser m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> (TodoSequence -> OrgParserState -> OrgParserState)
-> TodoSequence
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TodoSequence -> OrgParserState -> OrgParserState
registerTodoSequence
]
parseThen :: PandocMonad m
=> OrgParser m (F a)
-> (a -> Meta -> Meta)
-> OrgParser m ()
parseThen :: OrgParser m (F a) -> (a -> Meta -> Meta) -> OrgParser m ()
parseThen OrgParser m (F a)
p a -> Meta -> Meta
modMeta = do
F a
value <- OrgParser m (F a)
p
F Meta
meta <- OrgParserState -> F Meta
orgStateMeta (OrgParserState -> F Meta)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (F Meta)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\OrgParserState
st -> OrgParserState
st { orgStateMeta :: F Meta
orgStateMeta = a -> Meta -> Meta
modMeta (a -> Meta -> Meta) -> F a -> Future OrgParserState (Meta -> Meta)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F a
value Future OrgParserState (Meta -> Meta) -> F Meta -> F Meta
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> F Meta
meta })
collectLines :: Text -> Inlines -> Meta -> Meta
collectLines :: Text -> Inlines -> Meta -> Meta
collectLines Text
key Inlines
value Meta
meta =
let value' :: MetaValue
value' = Meta -> [Inline] -> MetaValue
appendValue Meta
meta (Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
value)
in Text -> MetaValue -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
key MetaValue
value' Meta
meta
where
appendValue :: Meta -> [Inline] -> MetaValue
appendValue :: Meta -> [Inline] -> MetaValue
appendValue Meta
m [Inline]
v = [Inline] -> MetaValue
MetaInlines ([Inline] -> MetaValue) -> [Inline] -> MetaValue
forall a b. (a -> b) -> a -> b
$ Meta -> [Inline]
curInlines Meta
m [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
v
curInlines :: Meta -> [Inline]
curInlines Meta
m = case MetaValue -> [Inline]
collectInlines (MetaValue -> [Inline]) -> Maybe MetaValue -> Maybe [Inline]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Meta -> Maybe MetaValue
lookupMeta Text
key Meta
m of
Maybe [Inline]
Nothing -> []
Just [] -> []
Just [Inline]
xs -> [Inline]
xs [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline
B.SoftBreak]
collectInlines :: MetaValue -> [Inline]
collectInlines :: MetaValue -> [Inline]
collectInlines = \case
MetaInlines [Inline]
inlns -> [Inline]
inlns
MetaList [MetaValue]
ml -> [Inline] -> [[Inline]] -> [Inline]
forall a. [a] -> [[a]] -> [a]
intercalate [Inline
B.SoftBreak] ([[Inline]] -> [Inline]) -> [[Inline]] -> [Inline]
forall a b. (a -> b) -> a -> b
$ (MetaValue -> [Inline]) -> [MetaValue] -> [[Inline]]
forall a b. (a -> b) -> [a] -> [b]
map MetaValue -> [Inline]
collectInlines [MetaValue]
ml
MetaString Text
s -> [Text -> Inline
B.Str Text
s]
MetaBlocks [Block]
blks -> [Block] -> [Inline]
blocksToInlines [Block]
blks
MetaMap Map Text MetaValue
_map -> []
MetaBool Bool
_bool -> []
collectAsList :: Text -> Inlines -> Meta -> Meta
collectAsList :: Text -> Inlines -> Meta -> Meta
collectAsList Text
key Inlines
value Meta
meta =
let value' :: MetaValue
value' = Meta -> MetaValue -> MetaValue
metaListAppend Meta
meta (Inlines -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
B.toMetaValue Inlines
value)
in Text -> MetaValue -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
B.setMeta Text
key MetaValue
value' Meta
meta
where
metaListAppend :: Meta -> MetaValue -> MetaValue
metaListAppend Meta
m MetaValue
v = [MetaValue] -> MetaValue
MetaList (Meta -> [MetaValue]
curList Meta
m [MetaValue] -> [MetaValue] -> [MetaValue]
forall a. [a] -> [a] -> [a]
++ [MetaValue
v])
curList :: Meta -> [MetaValue]
curList Meta
m = case Text -> Meta -> Maybe MetaValue
lookupMeta Text
key Meta
m of
Just (MetaList [MetaValue]
ms) -> [MetaValue]
ms
Just MetaValue
x -> [MetaValue
x]
Maybe MetaValue
_ -> []
metaExportSnippet :: Monad m => Text -> OrgParser m (F Inlines)
metaExportSnippet :: Text -> OrgParser m (F Inlines)
metaExportSnippet Text
format = Inlines -> F Inlines
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Inlines
B.rawInline Text
format (Text -> F Inlines)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
addLinkFormatter :: Monad m => OrgParser m ()
addLinkFormatter :: OrgParser m ()
addLinkFormatter = OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m () -> OrgParser m ())
-> OrgParser m () -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ do
Text
linkType <- Char -> Text -> Text
T.cons (Char -> Text -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
alphaNum ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"-_") ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
Text -> Text
formatter <- ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
forall (m :: * -> *). Monad m => OrgParser m (Text -> Text)
parseFormat
(OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> (OrgParserState -> OrgParserState) -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s ->
let fs :: OrgLinkFormatters
fs = OrgParserState -> OrgLinkFormatters
orgStateLinkFormatters OrgParserState
s
in OrgParserState
s{ orgStateLinkFormatters :: OrgLinkFormatters
orgStateLinkFormatters = Text -> (Text -> Text) -> OrgLinkFormatters -> OrgLinkFormatters
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Text
linkType Text -> Text
formatter OrgLinkFormatters
fs }
parseFormat :: Monad m => OrgParser m (Text -> Text)
parseFormat :: OrgParser m (Text -> Text)
parseFormat = OrgParser m (Text -> Text) -> OrgParser m (Text -> Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Text -> Text) -> OrgParser m (Text -> Text))
-> OrgParser m (Text -> Text) -> OrgParser m (Text -> Text)
forall a b. (a -> b) -> a -> b
$ OrgParser m (Text -> Text)
forall u. ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
replacePlain OrgParser m (Text -> Text)
-> OrgParser m (Text -> Text) -> OrgParser m (Text -> Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (Text -> Text)
forall u. ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
replaceUrl OrgParser m (Text -> Text)
-> OrgParser m (Text -> Text) -> OrgParser m (Text -> Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (Text -> Text)
forall u. ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
justAppend
where
replacePlain :: ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
replacePlain = ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text))
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall a b. (a -> b) -> a -> b
$ (\[Text]
x -> [Text] -> Text
T.concat ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> [Text] -> [Text]) -> [Text] -> Text -> [Text]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse [Text]
x)
([Text] -> Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsecT Text u (ReaderT OrgParserLocal m) Text]
-> ParsecT Text u (ReaderT OrgParserLocal m) [Text]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Char -> ParsecT Text u (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
Stream s m Char =>
Char -> ParserT s st m Text
tillSpecifier Char
's', ParsecT Text u (ReaderT OrgParserLocal m) Text
forall st. ParserT Text st (ReaderT OrgParserLocal m) Text
rest]
replaceUrl :: ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
replaceUrl = ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text))
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall a b. (a -> b) -> a -> b
$ (\[Text]
x -> [Text] -> Text
T.concat ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> [Text] -> [Text]) -> [Text] -> Text -> [Text]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse [Text]
x (Text -> [Text]) -> (Text -> Text) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
urlEncode (String -> String) -> (Text -> String) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
([Text] -> Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) [Text]
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsecT Text u (ReaderT OrgParserLocal m) Text]
-> ParsecT Text u (ReaderT OrgParserLocal m) [Text]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Char -> ParsecT Text u (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
Stream s m Char =>
Char -> ParserT s st m Text
tillSpecifier Char
'h', ParsecT Text u (ReaderT OrgParserLocal m) Text
forall st. ParserT Text st (ReaderT OrgParserLocal m) Text
rest]
justAppend :: ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
justAppend = ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text))
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) (Text -> Text -> Text)
-> ParsecT Text u (ReaderT OrgParserLocal m) Text
-> ParsecT Text u (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text u (ReaderT OrgParserLocal m) Text
forall st. ParserT Text st (ReaderT OrgParserLocal m) Text
rest
rest :: ParserT Text st (ReaderT OrgParserLocal m) Text
rest = ParserT Text st (ReaderT OrgParserLocal m) Char
-> ParserT Text st (ReaderT OrgParserLocal m) ()
-> ParserT Text st (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar ParserT Text st (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParserT Text st (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParserT Text st (ReaderT OrgParserLocal m) ()
-> ParserT Text st (ReaderT OrgParserLocal m) ()
-> ParserT Text st (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParserT Text st (ReaderT OrgParserLocal m) Char
-> ParserT Text st (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ String -> ParserT Text st (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
"\n\r")
tillSpecifier :: Char -> ParserT s st m Text
tillSpecifier Char
c = ParserT s st m Char -> ParserT s st m String -> ParserT s st m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar (String -> ParserT s st m Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\n\r") (ParserT s st m String -> ParserT s st m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParserT s st m String -> ParserT s st m String)
-> ParserT s st m String -> ParserT s st m String
forall a b. (a -> b) -> a -> b
$ String -> ParserT s st m String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string (Char
'%'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
cChar -> String -> String
forall a. a -> [a] -> [a]
:String
""))
tagList :: Monad m => OrgParser m [Tag]
tagList :: OrgParser m [Tag]
tagList = do
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
(Text -> Tag) -> [Text] -> [Tag]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Tag
Tag ([Text] -> [Tag])
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> OrgParser m [Tag]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgTagWord ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces) OrgParser m [Tag]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m [Tag]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
setExcludedTags :: [Tag] -> OrgParserState -> OrgParserState
setExcludedTags :: [Tag] -> OrgParserState -> OrgParserState
setExcludedTags [Tag]
tags OrgParserState
st =
let finalSet :: Set Tag
finalSet = if OrgParserState -> Bool
orgStateExcludeTagsChanged OrgParserState
st
then (Tag -> Set Tag -> Set Tag) -> Set Tag -> [Tag] -> Set Tag
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Tag -> Set Tag -> Set Tag
forall a. Ord a => a -> Set a -> Set a
Set.insert (OrgParserState -> Set Tag
orgStateExcludeTags OrgParserState
st) [Tag]
tags
else [Tag] -> Set Tag
forall a. Ord a => [a] -> Set a
Set.fromList [Tag]
tags
in OrgParserState
st { orgStateExcludeTags :: Set Tag
orgStateExcludeTags = Set Tag
finalSet, orgStateExcludeTagsChanged :: Bool
orgStateExcludeTagsChanged = Bool
True }
setSelectedTags :: [Tag] -> OrgParserState -> OrgParserState
setSelectedTags :: [Tag] -> OrgParserState -> OrgParserState
setSelectedTags [Tag]
tags OrgParserState
st =
let finalSet :: Set Tag
finalSet = if OrgParserState -> Bool
orgStateSelectTagsChanged OrgParserState
st
then (Tag -> Set Tag -> Set Tag) -> Set Tag -> [Tag] -> Set Tag
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Tag -> Set Tag -> Set Tag
forall a. Ord a => a -> Set a -> Set a
Set.insert (OrgParserState -> Set Tag
orgStateSelectTags OrgParserState
st) [Tag]
tags
else [Tag] -> Set Tag
forall a. Ord a => [a] -> Set a
Set.fromList [Tag]
tags
in OrgParserState
st { orgStateSelectTags :: Set Tag
orgStateSelectTags = Set Tag
finalSet, orgStateSelectTagsChanged :: Bool
orgStateSelectTagsChanged = Bool
True }
setEmphasisPreChar :: Maybe [Char] -> OrgParserState -> OrgParserState
setEmphasisPreChar :: Maybe String -> OrgParserState -> OrgParserState
setEmphasisPreChar Maybe String
csMb OrgParserState
st =
let preChars :: String
preChars = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe (OrgParserState -> String
orgStateEmphasisPostChars OrgParserState
defaultOrgParserState) Maybe String
csMb
in OrgParserState
st { orgStateEmphasisPreChars :: String
orgStateEmphasisPreChars = String
preChars }
setEmphasisPostChar :: Maybe [Char] -> OrgParserState -> OrgParserState
setEmphasisPostChar :: Maybe String -> OrgParserState -> OrgParserState
setEmphasisPostChar Maybe String
csMb OrgParserState
st =
let postChars :: String
postChars = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe (OrgParserState -> String
orgStateEmphasisPostChars OrgParserState
defaultOrgParserState) Maybe String
csMb
in OrgParserState
st { orgStateEmphasisPostChars :: String
orgStateEmphasisPostChars = String
postChars }
emphChars :: Monad m => OrgParser m (Maybe [Char])
emphChars :: OrgParser m (Maybe String)
emphChars = do
ParserT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
Text -> Maybe String
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe String)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
lineOfInlines :: PandocMonad m => OrgParser m (F Inlines)
lineOfInlines :: OrgParser m (F Inlines)
lineOfInlines = do
OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> OrgParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (F Inlines)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
todoSequence :: Monad m => OrgParser m TodoSequence
todoSequence :: OrgParser m TodoSequence
todoSequence = OrgParser m TodoSequence -> OrgParser m TodoSequence
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m TodoSequence -> OrgParser m TodoSequence)
-> OrgParser m TodoSequence -> OrgParser m TodoSequence
forall a b. (a -> b) -> a -> b
$ do
[Text]
todoKws <- OrgParser m [Text]
forall (m :: * -> *). Monad m => OrgParser m [Text]
todoKeywords
Maybe [Text]
doneKws <- OrgParser m [Text]
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe [Text])
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (OrgParser m [Text]
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe [Text]))
-> OrgParser m [Text]
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
todoDoneSep OrgParser m () -> OrgParser m [Text] -> OrgParser m [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m [Text]
forall (m :: * -> *). Monad m => OrgParser m [Text]
doneKeywords
OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
case Maybe [Text]
doneKws of
Just [Text]
done -> TodoSequence -> OrgParser m TodoSequence
forall (m :: * -> *) a. Monad m => a -> m a
return (TodoSequence -> OrgParser m TodoSequence)
-> TodoSequence -> OrgParser m TodoSequence
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text] -> TodoSequence
keywordsToSequence [Text]
todoKws [Text]
done
Maybe [Text]
Nothing -> case [Text] -> [Text]
forall a. [a] -> [a]
reverse [Text]
todoKws of
[] -> OrgParser m TodoSequence
forall (m :: * -> *) a. MonadPlus m => m a
mzero
(Text
x:[Text]
xs) -> TodoSequence -> OrgParser m TodoSequence
forall (m :: * -> *) a. Monad m => a -> m a
return (TodoSequence -> OrgParser m TodoSequence)
-> TodoSequence -> OrgParser m TodoSequence
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text] -> TodoSequence
keywordsToSequence ([Text] -> [Text]
forall a. [a] -> [a]
reverse [Text]
xs) [Text
x]
where
todoKeyword :: Monad m => OrgParser m Text
todoKeyword :: OrgParser m Text
todoKeyword = ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
nonspaceChar OrgParser m Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
todoKeywords :: Monad m => OrgParser m [Text]
todoKeywords :: OrgParser m [Text]
todoKeywords = OrgParser m [Text] -> OrgParser m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m [Text] -> OrgParser m [Text])
-> OrgParser m [Text] -> OrgParser m [Text]
forall a b. (a -> b) -> a -> b
$
let endOfKeywords :: ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
endOfKeywords = ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
todoDoneSep ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text 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 Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
in ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
todoKeyword (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text 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 Text OrgParserState (ReaderT OrgParserLocal m) ()
endOfKeywords)
doneKeywords :: Monad m => OrgParser m [Text]
doneKeywords :: OrgParser m [Text]
doneKeywords = OrgParser m [Text] -> OrgParser m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m [Text] -> OrgParser m [Text])
-> OrgParser m [Text] -> OrgParser m [Text]
forall a b. (a -> b) -> a -> b
$
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
todoKeyword ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
todoDoneSep) (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text 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 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline)
todoDoneSep :: Monad m => OrgParser m ()
todoDoneSep :: OrgParser m ()
todoDoneSep = ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ())
-> (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ())
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'|' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
skipSpaces1
keywordsToSequence :: [Text] -> [Text] -> TodoSequence
keywordsToSequence :: [Text] -> [Text] -> TodoSequence
keywordsToSequence [Text]
todo [Text]
done =
let todoMarkers :: TodoSequence
todoMarkers = (Text -> TodoMarker) -> [Text] -> TodoSequence
forall a b. (a -> b) -> [a] -> [b]
map (TodoState -> Text -> TodoMarker
TodoMarker TodoState
Todo) [Text]
todo
doneMarkers :: TodoSequence
doneMarkers = (Text -> TodoMarker) -> [Text] -> TodoSequence
forall a b. (a -> b) -> [a] -> [b]
map (TodoState -> Text -> TodoMarker
TodoMarker TodoState
Done) [Text]
done
in TodoSequence
todoMarkers TodoSequence -> TodoSequence -> TodoSequence
forall a. [a] -> [a] -> [a]
++ TodoSequence
doneMarkers
macroDefinition :: Monad m => OrgParser m (Text, [Text] -> Text)
macroDefinition :: OrgParser m (Text, [Text] -> Text)
macroDefinition = OrgParser m (Text, [Text] -> Text)
-> OrgParser m (Text, [Text] -> Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Text, [Text] -> Text)
-> OrgParser m (Text, [Text] -> Text))
-> OrgParser m (Text, [Text] -> Text)
-> OrgParser m (Text, [Text] -> Text)
forall a b. (a -> b) -> a -> b
$ do
Text
macroName <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
nonspaceChar ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces
Text
firstPart <- ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
expansionPart
([Int]
elemOrder, [Text]
parts) <- [(Int, Text)] -> ([Int], [Text])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Int, Text)] -> ([Int], [Text]))
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Int, Text)]
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) ([Int], [Text])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) (Int, Text)
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) [(Int, Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ((,) (Int -> Text -> (Int, Text))
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Text -> (Int, Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
placeholder ParsecT
Text
OrgParserState
(ReaderT OrgParserLocal m)
(Text -> (Int, Text))
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Text OrgParserState (ReaderT OrgParserLocal m) (Int, Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
expansionPart)
let expander :: [Text] -> Text
expander = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
alternate (Text
firstPartText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
parts) ([Text] -> [Text]) -> ([Text] -> [Text]) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Text] -> [Text]
reorder [Int]
elemOrder
(Text, [Text] -> Text) -> OrgParser m (Text, [Text] -> Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
macroName, [Text] -> Text
expander)
where
placeholder :: Monad m => OrgParser m Int
placeholder :: OrgParser m Int
placeholder = OrgParser m Int -> OrgParser m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Int -> OrgParser m Int)
-> (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m Int)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Int)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> (Text -> Maybe Int) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead) (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m Int)
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m Int
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'$' ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit
expansionPart :: Monad m => OrgParser m Text
expansionPart :: OrgParser m Text
expansionPart = OrgParser m Text -> OrgParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Text -> OrgParser m Text)
-> OrgParser m Text -> OrgParser m Text
forall a b. (a -> b) -> a -> b
$ ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Int
forall (m :: * -> *). Monad m => OrgParser m Int
placeholder ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> String
-> ParserT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\n\r")
alternate :: [a] -> [a] -> [a]
alternate :: [a] -> [a] -> [a]
alternate [] [a]
ys = [a]
ys
alternate [a]
xs [] = [a]
xs
alternate (a
x:[a]
xs) (a
y:[a]
ys) = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
alternate [a]
xs [a]
ys
reorder :: [Int] -> [Text] -> [Text]
reorder :: [Int] -> [Text] -> [Text]
reorder [Int]
perm [Text]
xs =
let element :: Int -> [Text]
element Int
n = Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
take Int
1 ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
drop (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Text]
xs
in (Int -> [Text]) -> [Int] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Int -> [Text]
element [Int]
perm