Better warnings for repeated ;;s
This commit is contained in:
parent
e909c8ac42
commit
af1bb93aba
|
@ -67,7 +67,7 @@ spacing = do
|
||||||
|
|
||||||
spacing1 = do
|
spacing1 = do
|
||||||
spacing <- spacing
|
spacing <- spacing
|
||||||
when (null spacing) $ fail "no spacing"
|
when (null spacing) $ fail "Expected whitespace"
|
||||||
return spacing
|
return spacing
|
||||||
|
|
||||||
prop_allspacing = isOk allspacing "#foo"
|
prop_allspacing = isOk allspacing "#foo"
|
||||||
|
@ -84,7 +84,7 @@ allspacing = do
|
||||||
|
|
||||||
allspacingOrFail = do
|
allspacingOrFail = do
|
||||||
s <- allspacing
|
s <- allspacing
|
||||||
when (null s) $ fail "Expected spaces"
|
when (null s) $ fail "Expected whitespace"
|
||||||
|
|
||||||
unicodeDoubleQuote = do
|
unicodeDoubleQuote = do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
|
@ -183,9 +183,9 @@ popContext = do
|
||||||
then do
|
then do
|
||||||
let (a:r) = v
|
let (a:r) = v
|
||||||
setCurrentContexts r
|
setCurrentContexts r
|
||||||
return [a]
|
return $ Just a
|
||||||
else
|
else
|
||||||
return []
|
return Nothing
|
||||||
|
|
||||||
pushContext c = do
|
pushContext c = do
|
||||||
v <- getCurrentContexts
|
v <- getCurrentContexts
|
||||||
|
@ -233,8 +233,8 @@ reluctantlyTill1 p end = do
|
||||||
attempting rest branch =
|
attempting rest branch =
|
||||||
(try branch >> rest) <|> rest
|
(try branch >> rest) <|> rest
|
||||||
|
|
||||||
orFail parser stuff =
|
orFail parser errorAction =
|
||||||
try (disregard parser) <|> (disregard stuff >> fail "nope")
|
try parser <|> (errorAction >>= fail)
|
||||||
|
|
||||||
wasIncluded p = option False (p >> return True)
|
wasIncluded p = option False (p >> return True)
|
||||||
|
|
||||||
|
@ -252,7 +252,7 @@ withContext entry p = do
|
||||||
popContext
|
popContext
|
||||||
return v
|
return v
|
||||||
<|> do -- p failed without consuming input, abort context
|
<|> do -- p failed without consuming input, abort context
|
||||||
popContext
|
v <- popContext
|
||||||
fail ""
|
fail ""
|
||||||
|
|
||||||
called s p = do
|
called s p = do
|
||||||
|
@ -295,7 +295,7 @@ readConditionContents single =
|
||||||
otherOp = try $ do
|
otherOp = try $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
s <- readOp
|
s <- readOp
|
||||||
when (s == "-a" || s == "-o") $ fail "Wrong operator"
|
when (s == "-a" || s == "-o") $ fail "Unexpected operator"
|
||||||
return $ TC_Binary id typ s
|
return $ TC_Binary id typ s
|
||||||
|
|
||||||
guardArithmetic = do
|
guardArithmetic = do
|
||||||
|
@ -308,12 +308,9 @@ readConditionContents single =
|
||||||
readCondUnaryExp = do
|
readCondUnaryExp = do
|
||||||
op <- readCondUnaryOp
|
op <- readCondUnaryOp
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
(do
|
(readCondWord >>= return . op) `orFail` do
|
||||||
arg <- readCondWord
|
parseProblemAt pos ErrorC 1019 "Expected this to be an argument to the unary condition."
|
||||||
return $ op arg)
|
return "Expected an argument for the unary operator"
|
||||||
<|> (do
|
|
||||||
parseProblemAt pos ErrorC 1019 "Expected this to be an argument to the unary condition."
|
|
||||||
fail "oops")
|
|
||||||
|
|
||||||
readCondUnaryOp = try $ do
|
readCondUnaryOp = try $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
@ -1479,6 +1476,7 @@ readIfClause = called "if expression" $ do
|
||||||
g_Fi `orFail` do
|
g_Fi `orFail` do
|
||||||
parseProblemAt pos ErrorC 1046 "Couldn't find 'fi' for this 'if'."
|
parseProblemAt pos ErrorC 1046 "Couldn't find 'fi' for this 'if'."
|
||||||
parseProblem ErrorC 1047 "Expected 'fi' matching previously mentioned 'if'."
|
parseProblem ErrorC 1047 "Expected 'fi' matching previously mentioned 'if'."
|
||||||
|
return "Expected 'fi'."
|
||||||
|
|
||||||
return $ T_IfExpression id ((condition, action):elifs) elses
|
return $ T_IfExpression id ((condition, action):elifs) elses
|
||||||
|
|
||||||
|
@ -1498,7 +1496,9 @@ readIfPart = do
|
||||||
parseProblemAt pos ErrorC 1049 "Did you forget the 'then' for this 'if'?"
|
parseProblemAt pos ErrorC 1049 "Did you forget the 'then' for this 'if'?"
|
||||||
|
|
||||||
called "then clause" $ do
|
called "then clause" $ do
|
||||||
g_Then `orFail` parseProblem ErrorC 1050 "Expected 'then'."
|
g_Then `orFail` do
|
||||||
|
parseProblem ErrorC 1050 "Expected 'then'."
|
||||||
|
return "Expected 'then'."
|
||||||
|
|
||||||
acceptButWarn g_Semi ErrorC 1051 "No semicolons directly after 'then'."
|
acceptButWarn g_Semi ErrorC 1051 "No semicolons directly after 'then'."
|
||||||
allspacing
|
allspacing
|
||||||
|
@ -1564,7 +1564,7 @@ readBraceGroup = called "brace group" $ do
|
||||||
list <- readTerm
|
list <- readTerm
|
||||||
char '}' <|> do
|
char '}' <|> do
|
||||||
parseProblem ErrorC 1056 "Expected a '}'. If you have one, try a ; or \\n in front of it."
|
parseProblem ErrorC 1056 "Expected a '}'. If you have one, try a ; or \\n in front of it."
|
||||||
fail "Unable to parse"
|
fail "Missing '}'"
|
||||||
return $ T_BraceGroup id list
|
return $ T_BraceGroup id list
|
||||||
|
|
||||||
prop_readWhileClause = isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done"
|
prop_readWhileClause = isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done"
|
||||||
|
@ -1589,7 +1589,9 @@ readDoGroup loopPos = do
|
||||||
try . lookAhead $ g_Done
|
try . lookAhead $ g_Done
|
||||||
parseProblemAt loopPos ErrorC 1057 "Did you forget the 'do' for this loop?")
|
parseProblemAt loopPos ErrorC 1057 "Did you forget the 'do' for this loop?")
|
||||||
|
|
||||||
g_Do `orFail` parseProblem ErrorC 1058 "Expected 'do'."
|
g_Do `orFail` do
|
||||||
|
parseProblem ErrorC 1058 "Expected 'do'."
|
||||||
|
return "Expected 'do'."
|
||||||
|
|
||||||
acceptButWarn g_Semi ErrorC 1059 "No semicolons directly after 'do'."
|
acceptButWarn g_Semi ErrorC 1059 "No semicolons directly after 'do'."
|
||||||
allspacing
|
allspacing
|
||||||
|
@ -1602,6 +1604,7 @@ readDoGroup loopPos = do
|
||||||
g_Done `orFail` do
|
g_Done `orFail` do
|
||||||
parseProblemAt pos ErrorC 1061 "Couldn't find 'done' for this 'do'."
|
parseProblemAt pos ErrorC 1061 "Couldn't find 'done' for this 'do'."
|
||||||
parseProblem ErrorC 1062 "Expected 'done' matching previously mentioned 'do'."
|
parseProblem ErrorC 1062 "Expected 'done' matching previously mentioned 'do'."
|
||||||
|
return "Expected 'done'."
|
||||||
return commands
|
return commands
|
||||||
|
|
||||||
|
|
||||||
|
@ -1714,7 +1717,10 @@ readCaseItem = called "case item" $ do
|
||||||
optional g_Lparen
|
optional g_Lparen
|
||||||
spacing
|
spacing
|
||||||
pattern <- readPattern
|
pattern <- readPattern
|
||||||
g_Rparen
|
void g_Rparen <|> do
|
||||||
|
parseProblem ErrorC 1085
|
||||||
|
"Did you forget to move the ;; after extending this case item?"
|
||||||
|
fail "Expected ) to open a new case item"
|
||||||
readLineBreak
|
readLineBreak
|
||||||
list <- (lookAhead readCaseSeparator >> return []) <|> readCompoundList
|
list <- (lookAhead readCaseSeparator >> return []) <|> readCompoundList
|
||||||
separator <- readCaseSeparator `attempting` do
|
separator <- readCaseSeparator `attempting` do
|
||||||
|
@ -1926,8 +1932,8 @@ tryParseWordToken keyword t = try $ do
|
||||||
"Scripts are case sensitive. Use '" ++ keyword ++ "', not '" ++ str ++ "'."
|
"Scripts are case sensitive. Use '" ++ keyword ++ "', not '" ++ str ++ "'."
|
||||||
return $ t id
|
return $ t id
|
||||||
|
|
||||||
anycaseString =
|
anycaseString str =
|
||||||
mapM anycaseChar
|
mapM anycaseChar str <?> str
|
||||||
where
|
where
|
||||||
anycaseChar c = char (toLower c) <|> char (toUpper c)
|
anycaseChar c = char (toLower c) <|> char (toUpper c)
|
||||||
|
|
||||||
|
@ -2094,20 +2100,21 @@ sortNotes = sortBy compareNotes
|
||||||
data ParseResult = ParseResult { parseResult :: Maybe (Token, Map.Map Id SourcePos), parseNotes :: [ParseNote] } deriving (Show)
|
data ParseResult = ParseResult { parseResult :: Maybe (Token, Map.Map Id SourcePos), parseNotes :: [ParseNote] } deriving (Show)
|
||||||
|
|
||||||
makeErrorFor parsecError =
|
makeErrorFor parsecError =
|
||||||
ParseNote (errorPos parsecError) ErrorC 1072 $ getStringFromParsec $ errorMessages parsecError
|
ParseNote (errorPos parsecError) ErrorC 1072 $
|
||||||
|
getStringFromParsec $ errorMessages parsecError
|
||||||
|
|
||||||
getStringFromParsec errors =
|
getStringFromParsec errors =
|
||||||
case map snd $ sortWith fst $ map f errors of
|
case map f errors of
|
||||||
r -> unwords (take 1 $ nub r) ++ " Fix any mentioned problems and try again."
|
r -> unwords (take 1 $ catMaybes $ reverse r) ++
|
||||||
where f err =
|
" Fix any mentioned problems and try again."
|
||||||
|
where
|
||||||
|
f err =
|
||||||
case err of
|
case err of
|
||||||
UnExpect s -> (1, unexpected s)
|
UnExpect s -> return $ unexpected s
|
||||||
SysUnExpect s -> (2, unexpected s)
|
SysUnExpect s -> return $ unexpected s
|
||||||
Expect s -> (3, "Expected " ++ s ++ ".")
|
Expect s -> return $ "Expected " ++ s ++ "."
|
||||||
Message s -> (4, s ++ ".")
|
Message s -> if null s then Nothing else return $ s ++ "."
|
||||||
wut "" = "eof"
|
unexpected s = "Unexpected " ++ (if null s then "eof" else s) ++ "."
|
||||||
wut x = x
|
|
||||||
unexpected s = "Unexpected " ++ wut s ++ "."
|
|
||||||
|
|
||||||
parseShell filename contents =
|
parseShell filename contents =
|
||||||
case rp (parseWithNotes readScript) filename contents of
|
case rp (parseWithNotes readScript) filename contents of
|
||||||
|
|
Loading…
Reference in New Issue