{-# LANGUAGE OverloadedStrings #-}
module Data.OrgMode.Parse.Attoparsec.Drawer.Generic
( parseDrawer
, parseDrawerDelim
, drawerEnd
)
where
import Control.Applicative ((*>), (<*))
import Data.Attoparsec.Text
import Data.Attoparsec.Types as Attoparsec
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.OrgMode.Parse.Attoparsec.Util as Util
import Data.OrgMode.Types
parseDrawer :: Attoparsec.Parser Text Drawer
parseDrawer =
Drawer <$>
parseDrawerName <*>
(Text.unlines <$> manyTill Util.nonHeadline drawerEnd)
parseDrawerName :: Attoparsec.Parser Text Text
parseDrawerName =
skipSpace *> skip (== ':') *>
takeWhile1 (/= ':') <*
skip (== ':') <* skipSpace
parseDrawerDelim :: Text -> Attoparsec.Parser Text Text
parseDrawerDelim v =
skipSpace *> skip (== ':') *>
asciiCI v <*
skip (== ':') <* Util.skipOnlySpace
drawerEnd :: Attoparsec.Parser Text Text
drawerEnd = parseDrawerDelim "END"