Correctly consider $'..' a literal (fixes #1242)
This commit is contained in:
parent
52e8a42d9d
commit
bfc32200e2
|
@ -23,6 +23,7 @@ import ShellCheck.AST
|
|||
|
||||
import Control.Monad.Writer
|
||||
import Control.Monad
|
||||
import Data.Char
|
||||
import Data.Functor
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
|
@ -226,8 +227,43 @@ getLiteralStringExt more = g
|
|||
g (T_SingleQuoted _ s) = return s
|
||||
g (T_Literal _ s) = return s
|
||||
g (T_ParamSubSpecialChar _ s) = return s
|
||||
g (T_DollarSingleQuoted _ s) = return $ decodeEscapes s
|
||||
g x = more x
|
||||
|
||||
-- Bash style $'..' decoding
|
||||
decodeEscapes ('\\':c:cs) =
|
||||
case c of
|
||||
'a' -> '\a' : rest
|
||||
'b' -> '\b' : rest
|
||||
'e' -> '\x1B' : rest
|
||||
'f' -> '\f' : rest
|
||||
'n' -> '\n' : rest
|
||||
'r' -> '\r' : rest
|
||||
't' -> '\t' : rest
|
||||
'v' -> '\v' : rest
|
||||
'\'' -> '\'' : rest
|
||||
'"' -> '"' : rest
|
||||
'\\' -> '\\' : rest
|
||||
'x' ->
|
||||
case cs of
|
||||
(x:y:more) ->
|
||||
if isHexDigit x && isHexDigit y
|
||||
then chr (16*(digitToInt x) + (digitToInt y)) : rest
|
||||
else '\\':c:rest
|
||||
_ | isOctDigit c ->
|
||||
let digits = take 3 $ takeWhile isOctDigit (c:cs)
|
||||
num = parseOct digits
|
||||
in (if num < 256 then chr num else '?') : rest
|
||||
_ -> '\\' : c : rest
|
||||
where
|
||||
rest = decodeEscapes cs
|
||||
parseOct = f 0
|
||||
where
|
||||
f n "" = n
|
||||
f n (c:rest) = f (n * 8 + digitToInt c) rest
|
||||
decodeEscapes (c:cs) = c : decodeEscapes cs
|
||||
decodeEscapes [] = []
|
||||
|
||||
-- Is this token a string literal?
|
||||
isLiteral t = isJust $ getLiteralString t
|
||||
|
||||
|
|
|
@ -515,6 +515,7 @@ prop_checkPrintfVar12= verify checkPrintfVar "printf '%s %s\\n' 1 2 3"
|
|||
prop_checkPrintfVar13= verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4"
|
||||
prop_checkPrintfVar14= verify checkPrintfVar "printf '%*s\\n' 1"
|
||||
prop_checkPrintfVar15= verifyNot checkPrintfVar "printf '%*s\\n' 1 2"
|
||||
prop_checkPrintfVar16= verifyNot checkPrintfVar "printf $'string'"
|
||||
checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
|
||||
f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest
|
||||
f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest
|
||||
|
|
Loading…
Reference in New Issue