module Data.OrgMode.Parse.Attoparsec.Headline
( headlineBelowDepth
, headlineDepth
, headingPriority
, parseStats
, parseTags
, mkTitleMeta
, TitleMeta
)
where
import Control.Applicative
import Data.Attoparsec.Text
import Data.Attoparsec.Types as Attoparsec (Parser)
import Data.Maybe
import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude hiding (takeWhile)
import Text.Printf
import Data.OrgMode.Parse.Attoparsec.Section
import qualified Data.OrgMode.Parse.Attoparsec.Time as OrgMode.Time
import Data.OrgMode.Parse.Attoparsec.Util
import Data.OrgMode.Types
newtype TitleMeta = TitleMeta (Text, Maybe Stats, Maybe [Tag])
deriving (Eq, Show)
headlineBelowDepth :: [Text]
-> Depth
-> Attoparsec.Parser Text Headline
headlineBelowDepth stateKeywords d = do
depth' <- headlineDepth d <* skipOnlySpace
stateKey <- option Nothing (Just <$> parseStateKeyword stateKeywords <* skipOnlySpace)
priority' <- option Nothing (Just <$> headingPriority <* skipOnlySpace)
tstamp <- option Nothing (Just <$> OrgMode.Time.parseTimestamp <* skipOnlySpace)
TitleMeta
( titleText
, stats'
, (fromMaybe [] -> tags')
) <- parseTitle
section' <- parseSection
subHeadlines' <- option [] $ many' (headlineBelowDepth stateKeywords (d + 1))
skipSpace
pure $ Headline
{ depth = depth'
, stateKeyword = stateKey
, priority = priority'
, title = titleText
, timestamp = tstamp
, stats = stats'
, tags = tags'
, section = section'
, subHeadlines = subHeadlines'
}
headlineDepth :: Depth -> Attoparsec.Parser Text Depth
headlineDepth (Depth d) = takeDepth >>= test
where
takeDepth = Text.length <$> takeWhile1 (== '*')
test n | n <= d = fail $ printf "Headline depth of %d cannot be higher than a depth constraint of %d" n d
| otherwise = pure $ Depth n
parseStateKeyword :: [Text] -> Attoparsec.Parser Text StateKeyword
parseStateKeyword (fmap string -> sk) = StateKeyword <$> choice sk
headingPriority :: Attoparsec.Parser Text Priority
headingPriority = start *> zipChoice <* end
where
zipChoice = choice (zipWith mkPParser "ABC" [A,B,C])
mkPParser c p = char c *> pure p
start = string "[#"
end = char ']'
parseTitle :: Attoparsec.Parser Text TitleMeta
parseTitle =
mkTitleMeta <$>
titleStart <*>
(optMeta parseStats) <*>
(optMeta parseTags) <*>
leftovers <* (endOfLine <|> endOfInput)
where
titleStart = takeTill (\c -> inClass "[:" c || isEndOfLine c)
leftovers = option mempty $ takeTill (== '\n')
optMeta p = option Nothing (Just <$> p <* skipOnlySpace)
mkTitleMeta :: Text
-> Maybe Stats
-> Maybe [Tag]
-> Text
-> TitleMeta
mkTitleMeta start stats' tags' leftovers =
TitleMeta ((cleanTitle start leftovers), stats', tags')
where
cleanTitle t l
| Text.null leftovers = Text.strip t
| otherwise = Text.append t l
parseStats :: Attoparsec.Parser Text Stats
parseStats = pct <|> frac
where
pct = StatsPct
<$> (char '[' *> decimal <* string "%]")
frac = StatsOf
<$> (char '[' *> decimal)
<*> (char '/' *> decimal <* char ']')
parseTags :: Attoparsec.Parser Text [Tag]
parseTags = tags' >>= test
where
tags' = (char ':' *> takeWhile (/= '\n'))
test t
| Text.null t = fail "no data after beginning ':'"
| Text.last t /= ':' = fail $ Text.unpack $ "expected ':' at end of tag list but got: " `Text.snoc` Text.last t
| Text.length t < 2 = fail $ Text.unpack $ "not a valid tag set: " <> t
| otherwise = pure (Text.splitOn ":" (Text.init t))