{-# LANGUAGE OverloadedStrings #-}
module Documentation.Haddock.Parser.Util (
takeUntil,
removeEscapes,
makeLabeled,
takeHorizontalSpace,
skipHorizontalSpace,
) where
import qualified Text.Parsec as Parsec
import qualified Data.Text as T
import Data.Text (Text)
import Control.Applicative
import Control.Monad (mfilter)
import Documentation.Haddock.Parser.Monad
import Prelude hiding (takeWhile)
import Data.Char (isSpace)
horizontalSpace :: [Char]
horizontalSpace = " \t\f\v\r"
skipHorizontalSpace :: Parser ()
skipHorizontalSpace = Parsec.skipMany (Parsec.oneOf horizontalSpace)
takeHorizontalSpace :: Parser Text
takeHorizontalSpace = takeWhile (Parsec.oneOf horizontalSpace)
makeLabeled :: (String -> Maybe String -> a) -> Text -> a
makeLabeled f input = case T.break isSpace $ removeEscapes $ T.strip input of
(uri, "") -> f (T.unpack uri) Nothing
(uri, label) -> f (T.unpack uri) (Just . T.unpack $ T.stripStart label)
removeEscapes :: Text -> Text
removeEscapes = T.unfoldr go
where
go :: Text -> Maybe (Char, Text)
go xs = case T.uncons xs of
Just ('\\',ys) -> T.uncons ys
unconsed -> unconsed
takeUntil :: Text -> Parser Text
takeUntil end_ = T.dropEnd (T.length end_) <$> requireEnd (scan p (False, end)) >>= gotSome
where
end = T.unpack end_
p :: (Bool, String) -> Char -> Maybe (Bool, String)
p acc c = case acc of
(True, _) -> Just (False, end)
(_, []) -> Nothing
(_, x:xs) | x == c -> Just (False, xs)
_ -> Just (c == '\\', end)
requireEnd = mfilter (T.isSuffixOf end_)
gotSome xs
| T.null xs = fail "didn't get any content"
| otherwise = return xs