{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Org.ExportSettings
( exportSettings
) where
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Logging (LogMessage (UnknownOrgExportOption))
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
import Control.Monad (mzero, void)
import Data.Char (toLower)
import Data.Maybe (listToMaybe)
import Data.Text (Text, unpack)
exportSettings :: PandocMonad m => OrgParser m ()
exportSettings :: OrgParser m ()
exportSettings = ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [()]
-> OrgParser m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [()]
-> OrgParser m ())
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [()]
-> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ OrgParser m ()
-> OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [()]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy OrgParser m ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
skipSpaces OrgParser m ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
exportSetting
type ExportSettingSetter a = a -> ExportSettings -> ExportSettings
exportSetting :: PandocMonad m => OrgParser m ()
exportSetting :: OrgParser m ()
exportSetting = [OrgParser m ()] -> OrgParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"^" (\Bool
val ExportSettings
es -> ExportSettings
es { exportSubSuperscripts :: Bool
exportSubSuperscripts = Bool
val })
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"'" (\Bool
val ExportSettings
es -> ExportSettings
es { exportSmartQuotes :: Bool
exportSmartQuotes = Bool
val })
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"*" (\Bool
val ExportSettings
es -> ExportSettings
es { exportEmphasizedText :: Bool
exportEmphasizedText = Bool
val })
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"-" (\Bool
val ExportSettings
es -> ExportSettings
es { exportSpecialStrings :: Bool
exportSpecialStrings = Bool
val })
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
":"
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"<"
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"\\n" (\Bool
val ExportSettings
es -> ExportSettings
es { exportPreserveBreaks :: Bool
exportPreserveBreaks = Bool
val })
, Text -> ExportSettingSetter ArchivedTreesOption -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter ArchivedTreesOption -> OrgParser m ()
archivedTreeSetting Text
"arch" (\ArchivedTreesOption
val ExportSettings
es -> ExportSettings
es { exportArchivedTrees :: ArchivedTreesOption
exportArchivedTrees = ArchivedTreesOption
val })
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"author" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithAuthor :: Bool
exportWithAuthor = Bool
val })
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"c"
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"creator" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithCreator :: Bool
exportWithCreator = Bool
val })
, Text
-> ExportSettingSetter (Either [Text] [Text]) -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text
-> ExportSettingSetter (Either [Text] [Text]) -> OrgParser m ()
complementableListSetting Text
"d" (\Either [Text] [Text]
val ExportSettings
es -> ExportSettings
es { exportDrawers :: Either [Text] [Text]
exportDrawers = Either [Text] [Text]
val })
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"date"
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"e" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithEntities :: Bool
exportWithEntities = Bool
val })
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"email" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithEmail :: Bool
exportWithEmail = Bool
val })
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"f" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithFootnotes :: Bool
exportWithFootnotes = Bool
val })
, Text -> ExportSettingSetter Int -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Int -> OrgParser m ()
integerSetting Text
"H" (\Int
val ExportSettings
es -> ExportSettings
es { exportHeadlineLevels :: Int
exportHeadlineLevels = Int
val })
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"inline"
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"num"
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"p" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithPlanning :: Bool
exportWithPlanning = Bool
val })
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"pri"
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"prop"
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"stat"
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"tags" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithTags :: Bool
exportWithTags = Bool
val })
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"tasks"
, Text -> ExportSettingSetter TeXExport -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter TeXExport -> OrgParser m ()
texSetting Text
"tex" (\TeXExport
val ExportSettings
es -> ExportSettings
es { exportWithLatex :: TeXExport
exportWithLatex = TeXExport
val })
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"timestamp"
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"title"
, Text -> OrgParser m ()
forall (m :: * -> *). Monad m => Text -> OrgParser m ()
ignoredSetting Text
"toc"
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"todo" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithTodoKeywords :: Bool
exportWithTodoKeywords = Bool
val })
, Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *).
Monad m =>
Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting Text
"|" (\Bool
val ExportSettings
es -> ExportSettings
es { exportWithTables :: Bool
exportWithTables = Bool
val })
, OrgParser m ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
ignoreAndWarn
] OrgParser m () -> String -> OrgParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"export setting"
genericExportSetting :: Monad m
=> OrgParser m a
-> Text
-> ExportSettingSetter a
-> OrgParser m ()
genericExportSetting :: OrgParser m a -> Text -> ExportSettingSetter a -> OrgParser m ()
genericExportSetting OrgParser m a
optionParser Text
settingIdentifier ExportSettingSetter a
setter = 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
Char
_ <- Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) u.
Stream s m Char =>
Text -> ParsecT s u m Text
textStr Text
settingIdentifier ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> 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
':'
a
value <- OrgParser m a
optionParser
(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
$ a -> OrgParserState -> OrgParserState
modifyExportSettings a
value
where
modifyExportSettings :: a -> OrgParserState -> OrgParserState
modifyExportSettings a
val OrgParserState
st =
OrgParserState
st { orgStateExportSettings :: ExportSettings
orgStateExportSettings = ExportSettingSetter a
setter a
val (ExportSettings -> ExportSettings)
-> (OrgParserState -> ExportSettings)
-> OrgParserState
-> ExportSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> ExportSettings
orgStateExportSettings (OrgParserState -> ExportSettings)
-> OrgParserState -> ExportSettings
forall a b. (a -> b) -> a -> b
$ OrgParserState
st }
booleanSetting :: Monad m => Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting :: Text -> ExportSettingSetter Bool -> OrgParser m ()
booleanSetting = OrgParser m Bool
-> Text -> ExportSettingSetter Bool -> OrgParser m ()
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> ExportSettingSetter a -> OrgParser m ()
genericExportSetting OrgParser m Bool
forall (m :: * -> *). Monad m => OrgParser m Bool
elispBoolean
integerSetting :: Monad m => Text -> ExportSettingSetter Int -> OrgParser m ()
integerSetting :: Text -> ExportSettingSetter Int -> OrgParser m ()
integerSetting = OrgParser m Int
-> Text -> ExportSettingSetter Int -> OrgParser m ()
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> ExportSettingSetter a -> OrgParser m ()
genericExportSetting OrgParser m Int
forall u. ParsecT Text u (ReaderT OrgParserLocal m) Int
parseInt
where
parseInt :: ParsecT Text u (ReaderT OrgParserLocal m) Int
parseInt = ParsecT Text u (ReaderT OrgParserLocal m) Int
-> ParsecT Text u (ReaderT OrgParserLocal m) Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Text u (ReaderT OrgParserLocal m) Int
-> ParsecT Text u (ReaderT OrgParserLocal m) Int)
-> ParsecT Text u (ReaderT OrgParserLocal m) Int
-> ParsecT Text u (ReaderT OrgParserLocal m) Int
forall a b. (a -> b) -> a -> b
$
ParsecT Text u (ReaderT OrgParserLocal m) Char
-> ParsecT Text u (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text u (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
digit ParsecT Text u (ReaderT OrgParserLocal m) String
-> (String -> ParsecT Text u (ReaderT OrgParserLocal m) Int)
-> ParsecT Text u (ReaderT OrgParserLocal m) Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ParsecT Text u (ReaderT OrgParserLocal m) Int
-> ((Int, String) -> ParsecT Text u (ReaderT OrgParserLocal m) Int)
-> Maybe (Int, String)
-> ParsecT Text u (ReaderT OrgParserLocal m) Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ParsecT Text u (ReaderT OrgParserLocal m) Int
forall (m :: * -> *) a. MonadPlus m => m a
mzero (Int -> ParsecT Text u (ReaderT OrgParserLocal m) Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ParsecT Text u (ReaderT OrgParserLocal m) Int)
-> ((Int, String) -> Int)
-> (Int, String)
-> ParsecT Text u (ReaderT OrgParserLocal m) Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, String) -> Int
forall a b. (a, b) -> a
fst) (Maybe (Int, String)
-> ParsecT Text u (ReaderT OrgParserLocal m) Int)
-> (String -> Maybe (Int, String))
-> String
-> ParsecT Text u (ReaderT OrgParserLocal m) Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, String)] -> Maybe (Int, String)
forall a. [a] -> Maybe a
listToMaybe ([(Int, String)] -> Maybe (Int, String))
-> (String -> [(Int, String)]) -> String -> Maybe (Int, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [(Int, String)]
forall a. Read a => ReadS a
reads
archivedTreeSetting :: Monad m
=> Text
-> ExportSettingSetter ArchivedTreesOption
-> OrgParser m ()
archivedTreeSetting :: Text -> ExportSettingSetter ArchivedTreesOption -> OrgParser m ()
archivedTreeSetting =
OrgParser m ArchivedTreesOption
-> Text
-> ExportSettingSetter ArchivedTreesOption
-> OrgParser m ()
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> ExportSettingSetter a -> OrgParser m ()
genericExportSetting (OrgParser m ArchivedTreesOption
-> Text
-> ExportSettingSetter ArchivedTreesOption
-> OrgParser m ())
-> OrgParser m ArchivedTreesOption
-> Text
-> ExportSettingSetter ArchivedTreesOption
-> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ OrgParser m ArchivedTreesOption
archivedTreesHeadlineSetting OrgParser m ArchivedTreesOption
-> OrgParser m ArchivedTreesOption
-> OrgParser m ArchivedTreesOption
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m ArchivedTreesOption
archivedTreesBoolean
where
archivedTreesHeadlineSetting :: OrgParser m ArchivedTreesOption
archivedTreesHeadlineSetting =
ArchivedTreesOption
ArchivedTreesHeadlineOnly ArchivedTreesOption
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ArchivedTreesOption
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
optionString Text
"headline"
archivedTreesBoolean :: OrgParser m ArchivedTreesOption
archivedTreesBoolean = OrgParser m ArchivedTreesOption -> OrgParser m ArchivedTreesOption
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m ArchivedTreesOption
-> OrgParser m ArchivedTreesOption)
-> OrgParser m ArchivedTreesOption
-> OrgParser m ArchivedTreesOption
forall a b. (a -> b) -> a -> b
$ do
Bool
exportBool <- OrgParser m Bool
forall (m :: * -> *). Monad m => OrgParser m Bool
elispBoolean
ArchivedTreesOption -> OrgParser m ArchivedTreesOption
forall (m :: * -> *) a. Monad m => a -> m a
return (ArchivedTreesOption -> OrgParser m ArchivedTreesOption)
-> ArchivedTreesOption -> OrgParser m ArchivedTreesOption
forall a b. (a -> b) -> a -> b
$
if Bool
exportBool
then ArchivedTreesOption
ArchivedTreesExport
else ArchivedTreesOption
ArchivedTreesNoExport
complementableListSetting :: Monad m
=> Text
-> ExportSettingSetter (Either [Text] [Text])
-> OrgParser m ()
complementableListSetting :: Text
-> ExportSettingSetter (Either [Text] [Text]) -> OrgParser m ()
complementableListSetting = OrgParser m (Either [Text] [Text])
-> Text
-> ExportSettingSetter (Either [Text] [Text])
-> OrgParser m ()
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> ExportSettingSetter a -> OrgParser m ()
genericExportSetting (OrgParser m (Either [Text] [Text])
-> Text
-> ExportSettingSetter (Either [Text] [Text])
-> OrgParser m ())
-> OrgParser m (Either [Text] [Text])
-> Text
-> ExportSettingSetter (Either [Text] [Text])
-> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ [OrgParser m (Either [Text] [Text])]
-> OrgParser m (Either [Text] [Text])
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ [Text] -> Either [Text] [Text]
forall a b. a -> Either a b
Left ([Text] -> Either [Text] [Text])
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> OrgParser m (Either [Text] [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]
complementTextList
, [Text] -> Either [Text] [Text]
forall a b. b -> Either a b
Right ([Text] -> Either [Text] [Text])
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) [Text]
-> OrgParser m (Either [Text] [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]
stringList
, (\Bool
b -> if Bool
b then [Text] -> Either [Text] [Text]
forall a b. a -> Either a b
Left [] else [Text] -> Either [Text] [Text]
forall a b. b -> Either a b
Right []) (Bool -> Either [Text] [Text])
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Bool
-> OrgParser m (Either [Text] [Text])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *). Monad m => OrgParser m Bool
elispBoolean
]
where
stringList :: Monad m => OrgParser m [Text]
stringList :: OrgParser m [Text]
stringList = 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
$
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 [Text] -> OrgParser m [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
elispText ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
spaces
OrgParser m [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')'
complementTextList :: Monad m => OrgParser m [Text]
complementTextList :: OrgParser m [Text]
complementTextList = 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
$
String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"(not "
ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> OrgParser m [Text] -> OrgParser m [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
-> OrgParser m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
elispText ParsecT Text OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st. Stream s m Char => ParserT s st m ()
spaces
OrgParser m [Text]
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')'
elispText :: Monad m => OrgParser m Text
elispText :: OrgParser m Text
elispText = 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
$
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 Text -> OrgParser 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) Char
-> OrgParser 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 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
alphaNum (Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"')
texSetting :: Monad m
=> Text
-> ExportSettingSetter TeXExport
-> OrgParser m ()
texSetting :: Text -> ExportSettingSetter TeXExport -> OrgParser m ()
texSetting = OrgParser m TeXExport
-> Text -> ExportSettingSetter TeXExport -> OrgParser m ()
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> ExportSettingSetter a -> OrgParser m ()
genericExportSetting (OrgParser m TeXExport
-> Text -> ExportSettingSetter TeXExport -> OrgParser m ())
-> OrgParser m TeXExport
-> Text
-> ExportSettingSetter TeXExport
-> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ OrgParser m TeXExport
texVerbatim OrgParser m TeXExport
-> OrgParser m TeXExport -> OrgParser m TeXExport
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m TeXExport
texBoolean
where
texVerbatim :: OrgParser m TeXExport
texVerbatim = TeXExport
TeXVerbatim TeXExport
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m TeXExport
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => Text -> OrgParser m Text
optionString Text
"verbatim"
texBoolean :: OrgParser m TeXExport
texBoolean = OrgParser m TeXExport -> OrgParser m TeXExport
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m TeXExport -> OrgParser m TeXExport)
-> OrgParser m TeXExport -> OrgParser m TeXExport
forall a b. (a -> b) -> a -> b
$ do
Bool
exportBool <- OrgParser m Bool
forall (m :: * -> *). Monad m => OrgParser m Bool
elispBoolean
TeXExport -> OrgParser m TeXExport
forall (m :: * -> *) a. Monad m => a -> m a
return (TeXExport -> OrgParser m TeXExport)
-> TeXExport -> OrgParser m TeXExport
forall a b. (a -> b) -> a -> b
$
if Bool
exportBool
then TeXExport
TeXExport
else TeXExport
TeXIgnore
ignoredSetting :: Monad m => Text -> OrgParser m ()
ignoredSetting :: Text -> OrgParser m ()
ignoredSetting Text
s = OrgParser m () -> OrgParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (() ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) u.
Stream s m Char =>
Text -> ParsecT s u m Text
textStr Text
s OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':' OrgParser m ()
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
-> OrgParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
nonspaceChar)
ignoreAndWarn :: PandocMonad m => OrgParser m ()
ignoreAndWarn :: OrgParser m ()
ignoreAndWarn = 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
opt <- 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
LogMessage -> OrgParser m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (Text -> LogMessage
UnknownOrgExportOption Text
opt)
() -> OrgParser m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
elispBoolean :: Monad m => OrgParser m Bool
elispBoolean :: OrgParser m Bool
elispBoolean = OrgParser m Bool -> OrgParser m Bool
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Bool -> OrgParser m Bool)
-> OrgParser m Bool -> OrgParser m Bool
forall a b. (a -> b) -> a -> b
$ do
String
value <- ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
nonspaceChar
Bool -> OrgParser m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> OrgParser m Bool) -> Bool -> OrgParser m Bool
forall a b. (a -> b) -> a -> b
$ case (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
value of
String
"nil" -> Bool
False
String
"{}" -> Bool
False
String
"()" -> Bool
False
String
_ -> Bool
True
optionString :: Monad m => Text -> OrgParser m Text
optionString :: Text -> OrgParser m Text
optionString Text
s = 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
$ do
String
_ <- String
-> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string (Text -> String
unpack Text
s)
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 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
<|> ParsecT Text OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
spaceChar)
Text -> OrgParser m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
s