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