module Css.Selector.Utils (
readIdentifier, encodeIdentifier
, isValidIdentifier, toIdentifier
, readCssString, encodeString, encodeText
) where
import Control.Arrow(first)
import Data.Char(chr, digitToInt, intToDigit, isAsciiLower, isAsciiUpper, isHexDigit, ord)
import Data.Text(Text, cons, pack, singleton, snoc)
import qualified Data.Text as T
_initLast :: [a] -> Maybe ([a], a)
_initLast [] = Nothing
_initLast (a:as) = Just (go as a)
where go [] x = ([], x)
go (y:ys) x = first (x:) (go ys y)
_isQuote :: Char -> Bool
_isQuote '"' = True
_isQuote '\'' = True
_isQuote _ = False
readCssString :: String
-> String
readCssString (c:xs) | _isQuote c = f
where f | Just (vs, c') <- _initLast xs = g c' vs
| otherwise = "The string literal should contain at least two quotation marks."
where g c' vs | c == c' = _readCssString c vs
| otherwise = "The start and end quotation mark should be the same."
readCssString _ = error "The string should start with an \" or ' and end with the same quotation."
_readCssString :: Char -> String -> String
_readCssString c' = go
where go [] = []
go ('\\':'\n':xs) = go xs
go ('\\':ca@(c:xs)) | c == c' = c : go xs
| otherwise = let ~(y,ys) = _parseEscape ca in y : go ys
go (x:xs) | x == c' = error "The string can not contain a " ++ show x ++ ", you should escape it."
| otherwise = x : go xs
readIdentifier :: String
-> String
readIdentifier = _readCssString '\\'
_notEncode :: Char -> Bool
_notEncode x = isAsciiLower x || isAsciiUpper x
encodeString :: Char
-> String
-> String
encodeString c' = (c' :) . go
where go [] = [c']
go (c:cs) | _notEncode c = c : go cs
| otherwise = '\\' : _showHex (ord c) (go cs)
encodeText :: Char
-> Text
-> Text
encodeText c' t = cons c' (snoc (T.concatMap _encodeCharacter t) c')
_encodeCharacter :: Char -> Text
_encodeCharacter c
| _notEncode c = singleton c
| otherwise = cons '\\' (pack (_showHex (ord c) ""))
encodeIdentifier :: Text
-> Text
encodeIdentifier = T.concatMap _encodeCharacter
_showHex :: Int -> ShowS
_showHex = go (6 :: Int)
where go 0 _ s = s
go k n rs = go (k-1) q (intToDigit r : rs)
where ~(q, r) = quotRem n 16
_parseEscape :: String -> (Char, String)
_parseEscape = go (6 :: Int) 0
where go 0 n cs = yield n cs
go _ n "" = yield n ""
go i n ca@(c:cs) | isHexDigit c = go (i-1) (16*n+digitToInt c) cs
| otherwise = yield n ca
yield n s = (chr n, s)
isValidIdentifier :: String
-> Bool
isValidIdentifier = not . null
toIdentifier :: (Text -> a)
-> String
-> a
toIdentifier f ident | isValidIdentifier ident = f (pack ident)
| otherwise = error ("The identifier " <> show ident <> " is not a valid identifier.")