{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
module Text.Pandoc.Readers.Org.DocumentTree
( documentTree
, unprunedHeadlineToBlocks
) where
import Control.Arrow ((***), first)
import Control.Monad (guard, mplus)
import Data.List (intersperse)
import Data.Maybe (mapMaybe)
import Data.Text (Text)
import Text.Pandoc.Builder (Blocks, Inlines)
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Readers.Org.BlockStarts
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
documentTree :: PandocMonad m
=> OrgParser m (F Blocks)
-> OrgParser m (F Inlines)
-> OrgParser m (F Headline)
documentTree :: forall (m :: * -> *).
PandocMonad m =>
OrgParser m (F Blocks)
-> OrgParser m (F Inlines) -> OrgParser m (F Headline)
documentTree OrgParser m (F Blocks)
blocks OrgParser m (F Inlines)
inline = do
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]
many ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
commentLine
Properties
properties <- Properties
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Properties
forall a. Monoid a => a
mempty ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
forall (m :: * -> *). Monad m => OrgParser m Properties
propertiesDrawer
F Blocks
initialBlocks <- OrgParser m (F Blocks)
blocks
Future OrgParserState [Headline]
headlines <- [F Headline] -> Future OrgParserState [Headline]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([F Headline] -> Future OrgParserState [Headline])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Headline]
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState [Headline])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (F Headline)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Headline]
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 Blocks)
-> OrgParser m (F Inlines) -> Int -> OrgParser m (F Headline)
forall (m :: * -> *).
PandocMonad m =>
OrgParser m (F Blocks)
-> OrgParser m (F Inlines) -> Int -> OrgParser m (F Headline)
headline OrgParser m (F Blocks)
blocks OrgParser m (F Inlines)
inline Int
1) ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
Future OrgParserState [Inline]
title <- (Meta -> [Inline])
-> Future OrgParserState Meta -> Future OrgParserState [Inline]
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Meta -> [Inline]
docTitle (Future OrgParserState Meta -> Future OrgParserState [Inline])
-> (OrgParserState -> Future OrgParserState Meta)
-> OrgParserState
-> Future OrgParserState [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> Future OrgParserState Meta
orgStateMeta (OrgParserState -> Future OrgParserState [Inline])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState [Inline])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
F Headline -> OrgParser m (F Headline)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Headline -> OrgParser m (F Headline))
-> F Headline -> OrgParser m (F Headline)
forall a b. (a -> b) -> a -> b
$ do
[Headline]
headlines' <- Future OrgParserState [Headline]
headlines
Blocks
initialBlocks' <- F Blocks
initialBlocks
[Inline]
title' <- Future OrgParserState [Inline]
title
Headline -> F Headline
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Headline
{ headlineLevel :: Int
headlineLevel = Int
0
, headlineTodoMarker :: Maybe TodoMarker
headlineTodoMarker = Maybe TodoMarker
forall a. Maybe a
Nothing
, headlineText :: Inlines
headlineText = [Inline] -> Inlines
forall a. [a] -> Many a
B.fromList [Inline]
title'
, headlineTags :: [Tag]
headlineTags = [Tag]
forall a. Monoid a => a
mempty
, headlinePlanning :: PlanningInfo
headlinePlanning = PlanningInfo
emptyPlanning
, headlineProperties :: Properties
headlineProperties = Properties
properties
, headlineContents :: Blocks
headlineContents = Blocks
initialBlocks'
, headlineChildren :: [Headline]
headlineChildren = [Headline]
headlines'
}
where
commentLine :: Monad m => OrgParser m ()
commentLine :: forall (m :: * -> *). Monad m => OrgParser m ()
commentLine = OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
commentLineStart OrgParser m ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser 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) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine
toTag :: Text -> Tag
toTag :: Text -> Tag
toTag = Text -> Tag
Tag
newtype PropertyKey = PropertyKey { PropertyKey -> Text
fromKey :: Text }
deriving (Int -> PropertyKey -> ShowS
[PropertyKey] -> ShowS
PropertyKey -> String
(Int -> PropertyKey -> ShowS)
-> (PropertyKey -> String)
-> ([PropertyKey] -> ShowS)
-> Show PropertyKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyKey -> ShowS
showsPrec :: Int -> PropertyKey -> ShowS
$cshow :: PropertyKey -> String
show :: PropertyKey -> String
$cshowList :: [PropertyKey] -> ShowS
showList :: [PropertyKey] -> ShowS
Show, PropertyKey -> PropertyKey -> Bool
(PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool) -> Eq PropertyKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyKey -> PropertyKey -> Bool
== :: PropertyKey -> PropertyKey -> Bool
$c/= :: PropertyKey -> PropertyKey -> Bool
/= :: PropertyKey -> PropertyKey -> Bool
Eq, Eq PropertyKey
Eq PropertyKey =>
(PropertyKey -> PropertyKey -> Ordering)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> PropertyKey)
-> (PropertyKey -> PropertyKey -> PropertyKey)
-> Ord PropertyKey
PropertyKey -> PropertyKey -> Bool
PropertyKey -> PropertyKey -> Ordering
PropertyKey -> PropertyKey -> PropertyKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PropertyKey -> PropertyKey -> Ordering
compare :: PropertyKey -> PropertyKey -> Ordering
$c< :: PropertyKey -> PropertyKey -> Bool
< :: PropertyKey -> PropertyKey -> Bool
$c<= :: PropertyKey -> PropertyKey -> Bool
<= :: PropertyKey -> PropertyKey -> Bool
$c> :: PropertyKey -> PropertyKey -> Bool
> :: PropertyKey -> PropertyKey -> Bool
$c>= :: PropertyKey -> PropertyKey -> Bool
>= :: PropertyKey -> PropertyKey -> Bool
$cmax :: PropertyKey -> PropertyKey -> PropertyKey
max :: PropertyKey -> PropertyKey -> PropertyKey
$cmin :: PropertyKey -> PropertyKey -> PropertyKey
min :: PropertyKey -> PropertyKey -> PropertyKey
Ord)
toPropertyKey :: Text -> PropertyKey
toPropertyKey :: Text -> PropertyKey
toPropertyKey = Text -> PropertyKey
PropertyKey (Text -> PropertyKey) -> (Text -> Text) -> Text -> PropertyKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower
newtype PropertyValue = PropertyValue { PropertyValue -> Text
fromValue :: Text }
toPropertyValue :: Text -> PropertyValue
toPropertyValue :: Text -> PropertyValue
toPropertyValue = Text -> PropertyValue
PropertyValue
isNonNil :: PropertyValue -> Bool
isNonNil :: PropertyValue -> Bool
isNonNil PropertyValue
p = Text -> Text
T.toLower (PropertyValue -> Text
fromValue PropertyValue
p) Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text
"()", Text
"{}", Text
"nil"]
type Properties = [(PropertyKey, PropertyValue)]
data Headline = Headline
{ Headline -> Int
headlineLevel :: Int
, Headline -> Maybe TodoMarker
headlineTodoMarker :: Maybe TodoMarker
, Headline -> Inlines
headlineText :: Inlines
, Headline -> [Tag]
headlineTags :: [Tag]
, Headline -> PlanningInfo
headlinePlanning :: PlanningInfo
, Headline -> Properties
headlineProperties :: Properties
, Headline -> Blocks
headlineContents :: Blocks
, Headline -> [Headline]
headlineChildren :: [Headline]
}
headline :: PandocMonad m
=> OrgParser m (F Blocks)
-> OrgParser m (F Inlines)
-> Int
-> OrgParser m (F Headline)
headline :: forall (m :: * -> *).
PandocMonad m =>
OrgParser m (F Blocks)
-> OrgParser m (F Inlines) -> Int -> OrgParser m (F Headline)
headline OrgParser m (F Blocks)
blocks OrgParser m (F Inlines)
inline Int
lvl = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
forall a b. (a -> b) -> a -> b
$ do
Int
level <- OrgParser m Int
forall (m :: * -> *). Monad m => OrgParser m Int
headerStart
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Int
lvl Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
level)
Maybe TodoMarker
todoKw <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Maybe TodoMarker)
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) TodoMarker
forall (m :: * -> *). Monad m => OrgParser m TodoMarker
todoKeyword
([F Inlines]
title, [Tag]
tags) <- OrgParser m (F Inlines)
-> OrgParser m [Tag] -> OrgParser m ([F Inlines], [Tag])
forall (m :: * -> *) a b.
Monad m =>
OrgParser m a -> OrgParser m b -> OrgParser m ([a], b)
manyThen OrgParser m (F Inlines)
inline OrgParser m [Tag]
forall (m :: * -> *). Monad m => OrgParser m [Tag]
endOfTitle
PlanningInfo
planning <- PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option PlanningInfo
emptyPlanning ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
forall (m :: * -> *). Monad m => OrgParser m PlanningInfo
planningInfo
Properties
properties <- Properties
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Properties
forall a. Monoid a => a
mempty ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
forall (m :: * -> *). Monad m => OrgParser m Properties
propertiesDrawer
F Blocks
contents <- OrgParser m (F Blocks)
blocks
[F Headline]
children <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Headline]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (OrgParser m (F Blocks)
-> OrgParser m (F Inlines)
-> Int
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
forall (m :: * -> *).
PandocMonad m =>
OrgParser m (F Blocks)
-> OrgParser m (F Inlines) -> Int -> OrgParser m (F Headline)
headline OrgParser m (F Blocks)
blocks OrgParser m (F Inlines)
inline (Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
F Headline
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Headline
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline))
-> F Headline
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Headline)
forall a b. (a -> b) -> a -> b
$ do
Inlines
title' <- F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF ([F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat [F Inlines]
title)
Blocks
contents' <- F Blocks
contents
[Headline]
children' <- [F Headline] -> Future OrgParserState [Headline]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [F Headline]
children
Headline -> F Headline
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Headline
{ headlineLevel :: Int
headlineLevel = Int
level
, headlineTodoMarker :: Maybe TodoMarker
headlineTodoMarker = Maybe TodoMarker
todoKw
, headlineText :: Inlines
headlineText = Inlines
title'
, headlineTags :: [Tag]
headlineTags = [Tag]
tags
, headlinePlanning :: PlanningInfo
headlinePlanning = PlanningInfo
planning
, headlineProperties :: Properties
headlineProperties = Properties
properties
, headlineContents :: Blocks
headlineContents = Blocks
contents'
, headlineChildren :: [Headline]
headlineChildren = [Headline]
children'
}
where
endOfTitle :: Monad m => OrgParser m [Tag]
endOfTitle :: forall (m :: * -> *). Monad m => OrgParser m [Tag]
endOfTitle = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
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
[Tag]
tags <- [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
forall (m :: * -> *). Monad m => OrgParser m [Tag]
headerTags ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
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)
OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
[Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return [Tag]
tags
headerTags :: Monad m => OrgParser m [Tag]
headerTags :: forall (m :: * -> *). Monad m => OrgParser m [Tag]
headerTags = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
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) Tag
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Tag]
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]
endBy1 (Text -> Tag
toTag (Text -> Tag)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Tag
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgTagWord) (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
':')
manyThen :: Monad m
=> OrgParser m a
-> OrgParser m b
-> OrgParser m ([a], b)
manyThen :: forall (m :: * -> *) a b.
Monad m =>
OrgParser m a -> OrgParser m b -> OrgParser m ([a], b)
manyThen OrgParser m a
p OrgParser m b
end = (([],) (b -> ([a], b))
-> OrgParser m b
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([a], b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m b -> OrgParser m b
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try OrgParser m b
end) ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ([a], b)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([a], b)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([a], b)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> do
a
x <- OrgParser m a
p
([a] -> [a]) -> ([a], b) -> ([a], b)
forall b c d. (b -> c) -> (b, d) -> (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:) (([a], b) -> ([a], b))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([a], b)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([a], b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m a
-> OrgParser m b
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([a], b)
forall (m :: * -> *) a b.
Monad m =>
OrgParser m a -> OrgParser m b -> OrgParser m ([a], b)
manyThen OrgParser m a
p OrgParser m b
end
unprunedHeadlineToBlocks :: Monad m => Headline -> OrgParserState -> OrgParser m [Block]
unprunedHeadlineToBlocks :: forall (m :: * -> *).
Monad m =>
Headline -> OrgParserState -> OrgParser m [Block]
unprunedHeadlineToBlocks Headline
hdln OrgParserState
st =
let usingSelectedTags :: Bool
usingSelectedTags = Headline -> OrgParserState -> Bool
docContainsSelectTags Headline
hdln OrgParserState
st
rootNode :: Headline
rootNode = if Bool -> Bool
not Bool
usingSelectedTags
then Headline
hdln
else Headline -> OrgParserState -> Headline
includeRootAndSelected Headline
hdln OrgParserState
st
rootNode' :: Headline
rootNode' = Headline -> OrgParserState -> Headline
removeExplicitlyExcludedNodes Headline
rootNode OrgParserState
st
in if Bool -> Bool
not Bool
usingSelectedTags Bool -> Bool -> Bool
||
(Tag -> Bool) -> [Tag] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Tag -> Set Tag -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` OrgParserState -> Set Tag
orgStateSelectTags OrgParserState
st) (Headline -> [Tag]
headlineTags Headline
rootNode')
then do Blocks
headlineBlocks <- Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToBlocks Headline
rootNode'
(OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s ->
OrgParserState
s{ orgStateMeta = foldr
(\(PropertyKey Text
k, PropertyValue Text
v) Future OrgParserState Meta
m ->
Text -> Text -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
k Text
v (Meta -> Meta)
-> Future OrgParserState Meta -> Future OrgParserState Meta
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future OrgParserState Meta
m)
(orgStateMeta s)
(headlineProperties rootNode') }
[Block] -> OrgParser m [Block]
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Block] -> OrgParser m [Block]) -> [Block] -> OrgParser m [Block]
forall a b. (a -> b) -> a -> b
$ Int -> [Block] -> [Block]
forall a. Int -> [a] -> [a]
drop Int
1 ([Block] -> [Block]) -> [Block] -> [Block]
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
headlineBlocks
else do Blocks
headlineBlocks <- [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Blocks]
-> OrgParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Headline -> OrgParser m Blocks)
-> [Headline]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToBlocks
(Headline -> [Headline]
headlineChildren Headline
rootNode')
[Block] -> OrgParser m [Block]
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Block] -> OrgParser m [Block])
-> (Blocks -> [Block]) -> Blocks -> OrgParser m [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [Block]
forall a. Many a -> [a]
B.toList (Blocks -> OrgParser m [Block]) -> Blocks -> OrgParser m [Block]
forall a b. (a -> b) -> a -> b
$ Blocks
headlineBlocks
headlineToBlocks :: Monad m => Headline -> OrgParser m Blocks
headlineToBlocks :: forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToBlocks Headline
hdln = do
Int
maxLevel <- (ExportSettings -> Int) -> OrgParser m Int
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Int
exportHeadlineLevels
let tags :: [Tag]
tags = Headline -> [Tag]
headlineTags Headline
hdln
let text :: Inlines
text = Headline -> Inlines
headlineText Headline
hdln
let level :: Int
level = Headline -> Int
headlineLevel Headline
hdln
case () of
()
_ | (Tag -> Bool) -> [Tag] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Tag -> Bool
isArchiveTag [Tag]
tags -> Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
archivedHeadlineToBlocks Headline
hdln
()
_ | Inlines -> Bool
isCommentTitle Inlines
text -> Blocks -> OrgParser m Blocks
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
()
_ | Int
maxLevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
level -> Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToHeaderWithList Headline
hdln
()
_ | Bool
otherwise -> Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToHeaderWithContents Headline
hdln
removeExplicitlyExcludedNodes :: Headline -> OrgParserState -> Headline
removeExplicitlyExcludedNodes :: Headline -> OrgParserState -> Headline
removeExplicitlyExcludedNodes Headline
hdln OrgParserState
st =
Headline
hdln { headlineChildren =
[removeExplicitlyExcludedNodes childHdln st |
childHdln <- headlineChildren hdln,
not $ headlineContainsExcludeTags childHdln st] }
includeRootAndSelected :: Headline -> OrgParserState -> Headline
includeRootAndSelected :: Headline -> OrgParserState -> Headline
includeRootAndSelected Headline
hdln OrgParserState
st =
Headline
hdln { headlineChildren = mapMaybe (`includeAncestorsAndSelected` st)
(headlineChildren hdln)}
docContainsSelectTags :: Headline -> OrgParserState -> Bool
docContainsSelectTags :: Headline -> OrgParserState -> Bool
docContainsSelectTags Headline
hdln OrgParserState
st =
Headline -> OrgParserState -> Bool
headlineContainsSelectTags Headline
hdln OrgParserState
st Bool -> Bool -> Bool
||
(Headline -> Bool) -> [Headline] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Headline -> OrgParserState -> Bool
`docContainsSelectTags` OrgParserState
st) (Headline -> [Headline]
headlineChildren Headline
hdln)
includeAncestorsAndSelected :: Headline -> OrgParserState -> Maybe Headline
includeAncestorsAndSelected :: Headline -> OrgParserState -> Maybe Headline
includeAncestorsAndSelected Headline
hdln OrgParserState
st =
if Headline -> OrgParserState -> Bool
headlineContainsSelectTags Headline
hdln OrgParserState
st
then Headline -> Maybe Headline
forall a. a -> Maybe a
Just Headline
hdln
else let children :: [Headline]
children = (Headline -> Maybe Headline) -> [Headline] -> [Headline]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Headline -> OrgParserState -> Maybe Headline
`includeAncestorsAndSelected` OrgParserState
st)
(Headline -> [Headline]
headlineChildren Headline
hdln)
in case [Headline]
children of
[] -> Maybe Headline
forall a. Maybe a
Nothing
[Headline]
_ -> Headline -> Maybe Headline
forall a. a -> Maybe a
Just (Headline -> Maybe Headline) -> Headline -> Maybe Headline
forall a b. (a -> b) -> a -> b
$ Headline
hdln { headlineChildren = children }
headlineContainsSelectTags :: Headline -> OrgParserState -> Bool
headlineContainsSelectTags :: Headline -> OrgParserState -> Bool
headlineContainsSelectTags Headline
hdln OrgParserState
st =
(Tag -> Bool) -> [Tag] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Tag -> Set Tag -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` OrgParserState -> Set Tag
orgStateSelectTags OrgParserState
st) (Headline -> [Tag]
headlineTags Headline
hdln)
headlineContainsExcludeTags :: Headline -> OrgParserState -> Bool
headlineContainsExcludeTags :: Headline -> OrgParserState -> Bool
headlineContainsExcludeTags Headline
hdln OrgParserState
st =
(Tag -> Bool) -> [Tag] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Tag -> Set Tag -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` OrgParserState -> Set Tag
orgStateExcludeTags OrgParserState
st) (Headline -> [Tag]
headlineTags Headline
hdln)
isArchiveTag :: Tag -> Bool
isArchiveTag :: Tag -> Bool
isArchiveTag = (Tag -> Tag -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Tag
toTag Text
"ARCHIVE")
isCommentTitle :: Inlines -> Bool
Inlines
inlns = case Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
inlns of
(Str Text
"COMMENT":[Inline]
_) -> Bool
True
[Inline]
_ -> Bool
False
archivedHeadlineToBlocks :: Monad m => Headline -> OrgParser m Blocks
archivedHeadlineToBlocks :: forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
archivedHeadlineToBlocks Headline
hdln = do
ArchivedTreesOption
archivedTreesOption <- (ExportSettings -> ArchivedTreesOption)
-> OrgParser m ArchivedTreesOption
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> ArchivedTreesOption
exportArchivedTrees
case ArchivedTreesOption
archivedTreesOption of
ArchivedTreesOption
ArchivedTreesNoExport -> Blocks -> OrgParser m Blocks
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
ArchivedTreesOption
ArchivedTreesExport -> Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToHeaderWithContents Headline
hdln
ArchivedTreesOption
ArchivedTreesHeadlineOnly -> Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToHeader Headline
hdln
headlineToHeaderWithList :: Monad m => Headline -> OrgParser m Blocks
Headline
hdln = do
Int
maxHeadlineLevels <- (ExportSettings -> Int) -> OrgParser m Int
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Int
exportHeadlineLevels
Blocks
header <- Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToHeader Headline
hdln
[Blocks]
listElements <- (Headline -> OrgParser m Blocks)
-> [Headline]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToBlocks (Headline -> [Headline]
headlineChildren Headline
hdln)
Blocks
planningBlock <- PlanningInfo -> OrgParser m Blocks
forall (m :: * -> *). Monad m => PlanningInfo -> OrgParser m Blocks
planningToBlock (Headline -> PlanningInfo
headlinePlanning Headline
hdln)
let listBlock :: Blocks
listBlock = if [Blocks] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Blocks]
listElements
then Blocks
forall a. Monoid a => a
mempty
else [Blocks] -> Blocks
B.orderedList [Blocks]
listElements
let headerText :: Blocks
headerText = if Int
maxHeadlineLevels Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Headline -> Int
headlineLevel Headline
hdln
then Blocks
header
else Blocks -> Blocks
flattenHeader Blocks
header
Blocks -> OrgParser m Blocks
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> OrgParser m Blocks)
-> ([Blocks] -> Blocks) -> [Blocks] -> OrgParser m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> OrgParser m Blocks) -> [Blocks] -> OrgParser m Blocks
forall a b. (a -> b) -> a -> b
$
[ Blocks
headerText
, Blocks
planningBlock
, Headline -> Blocks
headlineContents Headline
hdln
, Blocks
listBlock
]
where
flattenHeader :: Blocks -> Blocks
flattenHeader :: Blocks -> Blocks
flattenHeader Blocks
blks =
case Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
blks of
(Header Int
_ Attr
_ [Inline]
inlns:[Block]
_) -> Inlines -> Blocks
B.para ([Inline] -> Inlines
forall a. [a] -> Many a
B.fromList [Inline]
inlns)
[Block]
_ -> Blocks
forall a. Monoid a => a
mempty
headlineToHeaderWithContents :: Monad m => Headline -> OrgParser m Blocks
Headline
hdln = do
Blocks
header <- Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToHeader Headline
hdln
Blocks
planningBlock <- PlanningInfo -> OrgParser m Blocks
forall (m :: * -> *). Monad m => PlanningInfo -> OrgParser m Blocks
planningToBlock (Headline -> PlanningInfo
headlinePlanning Headline
hdln)
Blocks
childrenBlocks <- [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Blocks]
-> OrgParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Headline -> OrgParser m Blocks)
-> [Headline]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Headline -> OrgParser m Blocks
forall (m :: * -> *). Monad m => Headline -> OrgParser m Blocks
headlineToBlocks (Headline -> [Headline]
headlineChildren Headline
hdln)
Blocks -> OrgParser m Blocks
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> OrgParser m Blocks) -> Blocks -> OrgParser m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
header Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
planningBlock Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Headline -> Blocks
headlineContents Headline
hdln Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
childrenBlocks
headlineToHeader :: Monad m => Headline -> OrgParser m Blocks
Headline
hdln = do
Bool
exportTodoKeyword <- (ExportSettings -> Bool) -> OrgParser m Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportWithTodoKeywords
Bool
exportTags <- (ExportSettings -> Bool) -> OrgParser m Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportWithTags
let todoText :: Inlines
todoText = if Bool
exportTodoKeyword
then case Headline -> Maybe TodoMarker
headlineTodoMarker Headline
hdln of
Just TodoMarker
kw -> TodoMarker -> Inlines
todoKeywordToInlines TodoMarker
kw Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
Maybe TodoMarker
Nothing -> Inlines
forall a. Monoid a => a
mempty
else Inlines
forall a. Monoid a => a
mempty
let text :: Inlines
text = Inlines
todoText Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Headline -> Inlines
headlineText Headline
hdln Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
if Bool
exportTags
then [Tag] -> Inlines
tagsToInlines (Headline -> [Tag]
headlineTags Headline
hdln)
else Inlines
forall a. Monoid a => a
mempty
let propAttr :: Attr
propAttr = Properties -> Attr
propertiesToAttr (Headline -> Properties
headlineProperties Headline
hdln)
Attr
attr <- Attr
-> Inlines
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
HasIdentifierList st) =>
Attr -> Inlines -> ParsecT s st m Attr
registerHeader Attr
propAttr (Headline -> Inlines
headlineText Headline
hdln)
Blocks -> OrgParser m Blocks
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> OrgParser m Blocks) -> Blocks -> OrgParser m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Blocks
B.headerWith Attr
attr (Headline -> Int
headlineLevel Headline
hdln) Inlines
text
todoKeyword :: Monad m => OrgParser m TodoMarker
todoKeyword :: forall (m :: * -> *). Monad m => OrgParser m TodoMarker
todoKeyword = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
forall a b. (a -> b) -> a -> b
$ do
TodoSequence
taskStates <- OrgParserState -> TodoSequence
activeTodoMarkers (OrgParserState -> TodoSequence)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoSequence
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let kwParser :: TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
kwParser TodoMarker
tdm = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TodoMarker
tdm TodoMarker
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
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
<$ 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 (TodoMarker -> Text
todoMarkerName TodoMarker
tdm)
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
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 s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
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)
[ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ((TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker)
-> TodoSequence
-> [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker]
forall a b. (a -> b) -> [a] -> [b]
map TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
forall {m :: * -> *}.
Monad m =>
TodoMarker
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) TodoMarker
kwParser TodoSequence
taskStates)
todoKeywordToInlines :: TodoMarker -> Inlines
todoKeywordToInlines :: TodoMarker -> Inlines
todoKeywordToInlines TodoMarker
tdm =
let todoText :: Text
todoText = TodoMarker -> Text
todoMarkerName TodoMarker
tdm
todoState :: Text
todoState = Text -> Text
T.toLower (Text -> Text) -> (TodoState -> Text) -> TodoState -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (TodoState -> String) -> TodoState -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TodoState -> String
forall a. Show a => a -> String
show (TodoState -> Text) -> TodoState -> Text
forall a b. (a -> b) -> a -> b
$ TodoMarker -> TodoState
todoMarkerState TodoMarker
tdm
classes :: [Text]
classes = [Text
todoState, Text
todoText]
in Attr -> Inlines -> Inlines
B.spanWith (Text
forall a. Monoid a => a
mempty, [Text]
classes, [(Text, Text)]
forall a. Monoid a => a
mempty) (Text -> Inlines
B.str Text
todoText)
propertiesToAttr :: Properties -> Attr
propertiesToAttr :: Properties -> Attr
propertiesToAttr Properties
properties =
let
toTextPair :: (PropertyKey, PropertyValue) -> (Text, Text)
toTextPair = PropertyKey -> Text
fromKey (PropertyKey -> Text)
-> (PropertyValue -> Text)
-> (PropertyKey, PropertyValue)
-> (Text, Text)
forall b c b' c'. (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** PropertyValue -> Text
fromValue
customIdKey :: PropertyKey
customIdKey = Text -> PropertyKey
toPropertyKey Text
"custom_id"
idKey :: PropertyKey
idKey = Text -> PropertyKey
toPropertyKey Text
"id"
classKey :: PropertyKey
classKey = Text -> PropertyKey
toPropertyKey Text
"class"
unnumberedKey :: PropertyKey
unnumberedKey = Text -> PropertyKey
toPropertyKey Text
"unnumbered"
specialProperties :: [PropertyKey]
specialProperties = [PropertyKey
customIdKey, PropertyKey
idKey, PropertyKey
classKey, PropertyKey
unnumberedKey]
id' :: Text
id' = Text -> (PropertyValue -> Text) -> Maybe PropertyValue -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty PropertyValue -> Text
fromValue (Maybe PropertyValue -> Text) -> Maybe PropertyValue -> Text
forall a b. (a -> b) -> a -> b
$
(PropertyKey -> Properties -> Maybe PropertyValue
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup PropertyKey
customIdKey Properties
properties Maybe PropertyValue -> Maybe PropertyValue -> Maybe PropertyValue
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` PropertyKey -> Properties -> Maybe PropertyValue
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup PropertyKey
idKey Properties
properties)
cls :: Text
cls = Text -> (PropertyValue -> Text) -> Maybe PropertyValue -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty PropertyValue -> Text
fromValue (Maybe PropertyValue -> Text)
-> (Properties -> Maybe PropertyValue) -> Properties -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PropertyKey -> Properties -> Maybe PropertyValue
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup PropertyKey
classKey (Properties -> Text) -> Properties -> Text
forall a b. (a -> b) -> a -> b
$ Properties
properties
kvs' :: [(Text, Text)]
kvs' = ((PropertyKey, PropertyValue) -> (Text, Text))
-> Properties -> [(Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (PropertyKey, PropertyValue) -> (Text, Text)
toTextPair (Properties -> [(Text, Text)])
-> (Properties -> Properties) -> Properties -> [(Text, Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((PropertyKey, PropertyValue) -> Bool) -> Properties -> Properties
forall a. (a -> Bool) -> [a] -> [a]
filter ((PropertyKey -> [PropertyKey] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [PropertyKey]
specialProperties) (PropertyKey -> Bool)
-> ((PropertyKey, PropertyValue) -> PropertyKey)
-> (PropertyKey, PropertyValue)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PropertyKey, PropertyValue) -> PropertyKey
forall a b. (a, b) -> a
fst)
(Properties -> [(Text, Text)]) -> Properties -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Properties
properties
isUnnumbered :: Bool
isUnnumbered =
Bool -> (PropertyValue -> Bool) -> Maybe PropertyValue -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False PropertyValue -> Bool
isNonNil (Maybe PropertyValue -> Bool)
-> (Properties -> Maybe PropertyValue) -> Properties -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PropertyKey -> Properties -> Maybe PropertyValue
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup PropertyKey
unnumberedKey (Properties -> Bool) -> Properties -> Bool
forall a b. (a -> b) -> a -> b
$ Properties
properties
in
(Text
id', Text -> [Text]
T.words Text
cls [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"unnumbered" | Bool
isUnnumbered], [(Text, Text)]
kvs')
tagsToInlines :: [Tag] -> Inlines
tagsToInlines :: [Tag] -> Inlines
tagsToInlines [] = Inlines
forall a. Monoid a => a
mempty
tagsToInlines [Tag]
tags =
(Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>) (Inlines -> Inlines) -> ([Tag] -> Inlines) -> [Tag] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> ([Tag] -> [Inlines]) -> [Tag] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
B.str Text
"\160") ([Inlines] -> [Inlines])
-> ([Tag] -> [Inlines]) -> [Tag] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tag -> Inlines) -> [Tag] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Tag -> Inlines
tagToInline ([Tag] -> Inlines) -> [Tag] -> Inlines
forall a b. (a -> b) -> a -> b
$ [Tag]
tags
where
tagToInline :: Tag -> Inlines
tagToInline :: Tag -> Inlines
tagToInline Tag
t = Tag -> Inlines -> Inlines
tagSpan Tag
t (Inlines -> Inlines) -> (Text -> Inlines) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.smallcaps (Inlines -> Inlines) -> (Text -> Inlines) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Tag -> Text
fromTag Tag
t
tagSpan :: Tag -> Inlines -> Inlines
tagSpan :: Tag -> Inlines -> Inlines
tagSpan Tag
t = Attr -> Inlines -> Inlines
B.spanWith (Text
"", [Text
"tag"], [(Text
"tag-name", Tag -> Text
fromTag Tag
t)])
planningToBlock :: Monad m => PlanningInfo -> OrgParser m Blocks
planningToBlock :: forall (m :: * -> *). Monad m => PlanningInfo -> OrgParser m Blocks
planningToBlock PlanningInfo
planning = do
Bool
includePlanning <- (ExportSettings -> Bool) -> OrgParser m Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportWithPlanning
Blocks -> OrgParser m Blocks
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> OrgParser m Blocks) -> Blocks -> OrgParser m Blocks
forall a b. (a -> b) -> a -> b
$
if Bool
includePlanning
then Inlines -> Blocks
B.plain (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
B.space ([Inlines] -> [Inlines])
-> ([Inlines] -> [Inlines]) -> [Inlines] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inlines -> Bool) -> [Inlines] -> [Inlines]
forall a. (a -> Bool) -> [a] -> [a]
filter (Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
/= Inlines
forall a. Monoid a => a
mempty) ([Inlines] -> Blocks) -> [Inlines] -> Blocks
forall a b. (a -> b) -> a -> b
$
[ (PlanningInfo -> Maybe Text) -> Text -> Inlines
datumInlines PlanningInfo -> Maybe Text
planningClosed Text
"CLOSED"
, (PlanningInfo -> Maybe Text) -> Text -> Inlines
datumInlines PlanningInfo -> Maybe Text
planningDeadline Text
"DEADLINE"
, (PlanningInfo -> Maybe Text) -> Text -> Inlines
datumInlines PlanningInfo -> Maybe Text
planningScheduled Text
"SCHEDULED"
]
else Blocks
forall a. Monoid a => a
mempty
where
datumInlines :: (PlanningInfo -> Maybe Text) -> Text -> Inlines
datumInlines PlanningInfo -> Maybe Text
field Text
name =
case PlanningInfo -> Maybe Text
field PlanningInfo
planning of
Maybe Text
Nothing -> Inlines
forall a. Monoid a => a
mempty
Just Text
time -> Inlines -> Inlines
B.strong (Text -> Inlines
B.str Text
name Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.str Text
":")
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
B.emph (Text -> Inlines
B.str Text
time)
type Timestamp = Text
timestamp :: Monad m => OrgParser m Timestamp
timestamp :: forall (m :: * -> *). Monad m => OrgParser m Text
timestamp = 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
openChar <- String
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
"<["
let isActive :: Bool
isActive = Char
openChar Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'<'
let closeChar :: Char
closeChar = if Bool
isActive then Char
'>' else Char
']'
Text
content <- 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
anyChar (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
closeChar)
Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ Char -> Text -> Text
T.cons Char
openChar (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
content Text -> Char -> Text
`T.snoc` Char
closeChar
data PlanningInfo = PlanningInfo
{ PlanningInfo -> Maybe Text
planningClosed :: Maybe Timestamp
, PlanningInfo -> Maybe Text
planningDeadline :: Maybe Timestamp
, PlanningInfo -> Maybe Text
planningScheduled :: Maybe Timestamp
}
emptyPlanning :: PlanningInfo
emptyPlanning :: PlanningInfo
emptyPlanning = Maybe Text -> Maybe Text -> Maybe Text -> PlanningInfo
PlanningInfo Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing
planningInfo :: Monad m => OrgParser m PlanningInfo
planningInfo :: forall (m :: * -> *). Monad m => OrgParser m PlanningInfo
planningInfo = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
forall a b. (a -> b) -> a -> b
$ do
[PlanningInfo -> PlanningInfo]
updaters <- ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
[PlanningInfo -> PlanningInfo]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
planningDatum ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
[PlanningInfo -> PlanningInfo]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
[PlanningInfo -> PlanningInfo]
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)
[PlanningInfo -> PlanningInfo]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
[PlanningInfo -> PlanningInfo]
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
PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo)
-> PlanningInfo
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PlanningInfo
forall a b. (a -> b) -> a -> b
$ ((PlanningInfo -> PlanningInfo) -> PlanningInfo -> PlanningInfo)
-> PlanningInfo -> [PlanningInfo -> PlanningInfo] -> PlanningInfo
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (PlanningInfo -> PlanningInfo) -> PlanningInfo -> PlanningInfo
forall a b. (a -> b) -> a -> b
($) PlanningInfo
emptyPlanning [PlanningInfo -> PlanningInfo]
updaters
where
planningDatum :: ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
planningDatum = 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)
(PlanningInfo -> PlanningInfo)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
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)
(PlanningInfo -> PlanningInfo)]
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ (Text -> PlanningInfo -> PlanningInfo)
-> String
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
forall {m :: * -> *} {b}.
Monad m =>
(Text -> b)
-> String
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
updateWith (\Text
s PlanningInfo
p -> PlanningInfo
p { planningScheduled = Just s}) String
"SCHEDULED"
, (Text -> PlanningInfo -> PlanningInfo)
-> String
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
forall {m :: * -> *} {b}.
Monad m =>
(Text -> b)
-> String
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
updateWith (\Text
d PlanningInfo
p -> PlanningInfo
p { planningDeadline = Just d}) String
"DEADLINE"
, (Text -> PlanningInfo -> PlanningInfo)
-> String
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PlanningInfo -> PlanningInfo)
forall {m :: * -> *} {b}.
Monad m =>
(Text -> b)
-> String
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
updateWith (\Text
c PlanningInfo
p -> PlanningInfo
p { planningClosed = Just c}) String
"CLOSED"
]
updateWith :: (Text -> b)
-> String
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
updateWith Text -> b
fn String
cs = Text -> b
fn (Text -> b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
cs ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) String
-> 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) ()
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 (m :: * -> *). Monad m => OrgParser m Text
timestamp)
propertiesDrawer :: Monad m => OrgParser m Properties
propertiesDrawer :: forall (m :: * -> *). Monad m => OrgParser m Properties
propertiesDrawer = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
forall a b. (a -> b) -> a -> b
$ do
Text
drawerType <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
drawerStart
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toUpper Text
drawerType Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"PROPERTIES"
ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
-> OrgParser m Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Properties
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
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
forall (m :: * -> *).
Monad m =>
OrgParser m (PropertyKey, PropertyValue)
property (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
forall (m :: * -> *). Monad m => OrgParser m Text
endOfDrawer)
where
property :: Monad m => OrgParser m (PropertyKey, PropertyValue)
property :: forall (m :: * -> *).
Monad m =>
OrgParser m (PropertyKey, PropertyValue)
property = ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue))
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
forall a b. (a -> b) -> a -> b
$ (,) (PropertyKey -> PropertyValue -> (PropertyKey, PropertyValue))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyKey
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyValue -> (PropertyKey, PropertyValue))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyKey
forall (m :: * -> *). Monad m => OrgParser m PropertyKey
key ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyValue -> (PropertyKey, PropertyValue))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyValue
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(PropertyKey, PropertyValue)
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) PropertyValue
forall (m :: * -> *). Monad m => OrgParser m PropertyValue
value
key :: Monad m => OrgParser m PropertyKey
key :: forall (m :: * -> *). Monad m => OrgParser m PropertyKey
key = (Text -> PropertyKey)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyKey
forall a b.
(a -> b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> PropertyKey
toPropertyKey (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyKey)
-> (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) PropertyKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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) PropertyKey)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyKey
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
':' 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) 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 s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar (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
$ 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) 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
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar)
value :: Monad m => OrgParser m PropertyValue
value :: forall (m :: * -> *). Monad m => OrgParser m PropertyValue
value = (Text -> PropertyValue)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyValue
forall a b.
(a -> b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> PropertyValue
toPropertyValue (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyValue)
-> (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) PropertyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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) PropertyValue)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) PropertyValue
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) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (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
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline)
endOfDrawer :: Monad m => OrgParser m Text
endOfDrawer :: forall (m :: * -> *). Monad m => OrgParser m Text
endOfDrawer = 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
*> 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
stringAnyCase Text
":END:" 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