{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Cheapskate.Util (
joinLines
, tabFilter
, isWhitespace
, isEscapable
, normalizeReference
, Scanner
, scanIndentSpace
, scanNonindentSpace
, scanSpacesToColumn
, scanChar
, scanBlankline
, scanSpaces
, scanSpnl
, nfb
, nfbChar
, upToCountChars
) where
import Data.Text (Text)
import qualified Data.Text as T
import Data.Char
#if ! MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
import Cheapskate.ParserCombinators
joinLines :: [Text] -> Text
joinLines = T.intercalate "\n"
tabFilter :: Text -> Text
tabFilter = T.concat . pad . T.split (== '\t')
where pad [] = []
pad [t] = [t]
pad (t:ts) = let tl = T.length t
n = tl + 4 - (tl `mod` 4)
in T.justifyLeft n ' ' t : pad ts
isWhitespace :: Char -> Bool
isWhitespace ' ' = True
isWhitespace '\t' = True
isWhitespace '\n' = True
isWhitespace '\r' = True
isWhitespace _ = False
isEscapable :: Char -> Bool
isEscapable c = isAscii c && (isSymbol c || isPunctuation c)
normalizeReference :: Text -> Text
normalizeReference = T.toCaseFold . T.concat . T.split isWhitespace
type Scanner = Parser ()
scanIndentSpace :: Scanner
scanIndentSpace = () <$ count 4 (skip (==' '))
scanSpacesToColumn :: Int -> Scanner
scanSpacesToColumn col = do
currentCol <- column <$> getPosition
case col - currentCol of
n | n >= 1 -> () <$ (count n (skip (==' ')))
| otherwise -> return ()
scanNonindentSpace :: Scanner
scanNonindentSpace = () <$ upToCountChars 3 (==' ')
scanChar :: Char -> Scanner
scanChar c = skip (== c) >> return ()
scanBlankline :: Scanner
scanBlankline = scanSpaces *> endOfInput
scanSpaces :: Scanner
scanSpaces = skipWhile (==' ')
scanSpnl :: Scanner
scanSpnl = scanSpaces *> option () (char '\n' *> scanSpaces)
nfb :: Parser a -> Scanner
nfb = notFollowedBy
nfbChar :: Char -> Scanner
nfbChar c = nfb (skip (==c))
upToCountChars :: Int -> (Char -> Bool) -> Parser Text
upToCountChars cnt f =
scan 0 (\n c -> if n < cnt && f c then Just (n+1) else Nothing)