module Darcs.Util.CommandLine
( parseCmd
, addUrlencoded
) where
import Darcs.Prelude
import Control.Arrow ( (***) )
import Data.Char ( ord, intToDigit, toUpper )
import Data.List ( find )
import Text.ParserCombinators.Parsec
type FTable = [(Char,String)]
commandline :: FTable -> Parser ([String], Bool)
commandline ftable = consumeAll $ do
l <- sepEndBy1 (arg ftable) (try separator)
redir <- formatRedir
spaces
return (l,redir)
arg :: FTable -> Parser String
arg ftable = quotedArg ftable <|> unquotedArg ftable
unquotedArg :: FTable -> Parser String
unquotedArg ftable = try (format ftable) <|> many1 (noneOf " \t\"%")
quotedArg :: FTable -> Parser String
quotedArg ftable = between quoteChar quoteChar $ quoteContent ftable
where
quoteChar = char '"'
quoteContent :: FTable -> Parser String
quoteContent ftable = do s1 <- escape
<|> try (format ftable)
<|> many1 (noneOf "\"\\%")
s2 <- quoteContent ftable
return $ s1 ++ s2
<|> return ""
formatRedir :: Parser Bool
formatRedir = (string "%<" >> return True)
<|> return False
format :: FTable -> Parser String
format ftable = do _ <- char '%'
c <- oneOf (map fst ftable)
return $ expandFormat ftable c
escape :: Parser String
escape = do _ <- char '\\'
c <- anyChar
return [c]
consumeAll :: Parser a -> Parser a
consumeAll p = do r <- p
eof
return r
separator :: Parser ()
separator = skipMany1 space
expandFormat :: FTable -> Char -> String
expandFormat ftable c = case find ((==c) . fst) ftable of
Just (_,s) -> s
Nothing -> error "impossible"
parseCmd :: FTable -> String -> Either ParseError ([String],Bool)
parseCmd ftable = parse (commandline ftable) ""
urlEncode :: String -> String
urlEncode = concatMap escapeC
where escapeC x = if allowed x then [x] else '%' : intToHex (ord x)
intToHex i = map intToDigit [i `div` 16, i `mod` 16]
allowed x = x `elem` allowedChars
allowedChars = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ "!'()*-.~"
addUrlencoded :: FTable -> FTable
addUrlencoded ftable = ftable ++ map (toUpper *** urlEncode) ftable