Skip to content

Commit

Permalink
Resolve #9098: Add LexBraces lexer warning (#9099)
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej authored Oct 2, 2023
1 parent d363088 commit bbbca4f
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 8 deletions.
15 changes: 10 additions & 5 deletions Cabal-syntax/src/Distribution/Fields/LexerMonad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,8 @@ data LexWarningType
LexWarningTab
| -- | indentation decreases
LexInconsistentIndentation
| -- | Brace syntax used
LexBraces
deriving (Eq, Ord, Show)

data LexWarning
Expand All @@ -79,19 +81,22 @@ data LexWarning

toPWarnings :: [LexWarning] -> [PWarning]
toPWarnings =
map (uncurry toWarning)
mapMaybe (uncurry toWarning)
. Map.toList
. Map.fromListWith (flip (<>)) -- fromListWith gives existing element first.
. map (\(LexWarning t p) -> (t, pure p))
where
toWarning LexWarningBOM poss =
PWarning PWTLexBOM (NE.head poss) "Byte-order mark found at the beginning of the file"
Just $ PWarning PWTLexBOM (NE.head poss) "Byte-order mark found at the beginning of the file"
toWarning LexWarningNBSP poss =
PWarning PWTLexNBSP (NE.head poss) $ "Non breaking spaces at " ++ intercalate ", " (NE.toList $ fmap showPos poss)
Just $ PWarning PWTLexNBSP (NE.head poss) $ "Non breaking spaces at " ++ intercalate ", " (NE.toList $ fmap showPos poss)
toWarning LexWarningTab poss =
PWarning PWTLexTab (NE.head poss) $ "Tabs used as indentation at " ++ intercalate ", " (NE.toList $ fmap showPos poss)
Just $ PWarning PWTLexTab (NE.head poss) $ "Tabs used as indentation at " ++ intercalate ", " (NE.toList $ fmap showPos poss)
toWarning LexInconsistentIndentation poss =
PWarning PWTInconsistentIndentation (NE.head poss) $ "Inconsistent indentation. Indentation jumps at lines " ++ intercalate ", " (NE.toList $ fmap (show . positionRow) poss)
Just $ PWarning PWTInconsistentIndentation (NE.head poss) $ "Inconsistent indentation. Indentation jumps at lines " ++ intercalate ", " (NE.toList $ fmap (show . positionRow) poss)
-- LexBraces warning about using { } delimeters is not reported as parser warning.
toWarning LexBraces _ =
Nothing

{- FOURMOLU_DISABLE -}
data LexState = LexState
Expand Down
14 changes: 11 additions & 3 deletions Cabal-syntax/src/Distribution/Fields/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,11 @@ getLexerWarnings = do
LexState' (LexState{warnings = ws}) _ <- getInput
return ws

addLexerWarning :: LexWarning -> Parser ()
addLexerWarning w = do
LexState' ls@LexState{warnings = ws} _ <- getInput
setInput $! mkLexState' ls{warnings = w : ws}

-- | Set Alex code i.e. the mode "state" lexer is in.
setLexerMode :: Int -> Parser ()
setLexerMode code = do
Expand Down Expand Up @@ -118,15 +123,16 @@ describeToken t = case t of
tokSym :: Parser (Name Position)
tokSym', tokStr, tokOther :: Parser (SectionArg Position)
tokIndent :: Parser Int
tokColon, tokOpenBrace, tokCloseBrace :: Parser ()
tokColon, tokCloseBrace :: Parser ()
tokOpenBrace :: Parser Position
tokFieldLine :: Parser (FieldLine Position)
tokSym = getTokenWithPos $ \t -> case t of L pos (TokSym x) -> Just (mkName pos x); _ -> Nothing
tokSym' = getTokenWithPos $ \t -> case t of L pos (TokSym x) -> Just (SecArgName pos x); _ -> Nothing
tokStr = getTokenWithPos $ \t -> case t of L pos (TokStr x) -> Just (SecArgStr pos x); _ -> Nothing
tokOther = getTokenWithPos $ \t -> case t of L pos (TokOther x) -> Just (SecArgOther pos x); _ -> Nothing
tokIndent = getToken $ \t -> case t of Indent x -> Just x; _ -> Nothing
tokColon = getToken $ \t -> case t of Colon -> Just (); _ -> Nothing
tokOpenBrace = getToken $ \t -> case t of OpenBrace -> Just (); _ -> Nothing
tokOpenBrace = getTokenWithPos $ \t -> case t of L pos OpenBrace -> Just pos; _ -> Nothing
tokCloseBrace = getToken $ \t -> case t of CloseBrace -> Just (); _ -> Nothing
tokFieldLine = getTokenWithPos $ \t -> case t of L pos (TokFieldLine s) -> Just (FieldLine pos s); _ -> Nothing

Expand All @@ -138,7 +144,9 @@ fieldSecName :: Parser (Name Position)
fieldSecName = tokSym <?> "field or section name"

colon = tokColon <?> "\":\""
openBrace = tokOpenBrace <?> "\"{\""
openBrace = do
pos <- tokOpenBrace <?> "\"{\""
addLexerWarning (LexWarning LexBraces pos)
closeBrace = tokCloseBrace <?> "\"}\""

fieldContent :: Parser (FieldLine Position)
Expand Down
18 changes: 18 additions & 0 deletions changelog.d/issue-9098-lexbraces
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
synopsis: Add LexBraces lexer warning
packages: Cabal-syntax
issues: #8577

description: {

LexBraces warning is issued when brace delimiting syntax is used.
This way, using `readFields'`, a low-lever consumer may decide
whether braces were used.

(Looking for a brace character in the input is imprecise, as braces can occur inside field content).

This warning is not propagated to parser warnings,
so e.g. readGenericPackageDescription doesn't warn about it.
This is because all parser warnings prevent uploads to Hackage,
and using braces (or not) is opinionated choice.

}

0 comments on commit bbbca4f

Please sign in to comment.