Skip to content

Commit

Permalink
Make a trailing colon for stanzas a parse failure
Browse files Browse the repository at this point in the history
Here's a mistake I make semi-regularly:

    source-repository-package:
        type: git
        location: https://github.com/parsonsmatt/foundation
        tag: 688c32ccd9a951bc96dd09423a6e6684f091d510
        subdir: basement
        subdir: foundation

Cabal treats this as a warning, so it prints:

    Warning: cabal.project: Unrecognized field
    'source-repository-package' on line 52

This is fine (if you already know the mistake you've made, at least!),
but it's very easy to miss amidst lots of output.

I often re-run `cabal` when I see a ton of output to attempt to get a
smaller error message. (Usually it works and I get an error message
that's got less "compiling module such and such" noise in it.) However,
re-running `cabal` will discard this warning entirely!

Let's make it a hard error instead. This is a backwards-compatibility
break.
  • Loading branch information
9999years committed Nov 18, 2024
1 parent f4c0583 commit f34aba9
Show file tree
Hide file tree
Showing 7 changed files with 51 additions and 7 deletions.
20 changes: 13 additions & 7 deletions cabal-install/src/Distribution/Client/ParseUtils.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

-----------------------------------------------------------------------------

Expand Down Expand Up @@ -53,6 +55,7 @@ import Distribution.Deprecated.ParseUtils
( Field (..)
, FieldDescr (..)
, LineNo
, PError (..)
, ParseResult (..)
, liftField
, lineNo
Expand Down Expand Up @@ -292,13 +295,16 @@ parseFieldsAndSections fieldDescrs sectionDescrs fgSectionDescrs =
setField a (F line name value) =
case Map.lookup name fieldMap of
Just (FieldDescr _ _ set) -> set line value a
Nothing -> do
warning $
"Unrecognized field '"
++ name
++ "' on line "
++ show line
return a
Nothing ->
case Left <$> Map.lookup name sectionMap <|> Right <$> Map.lookup name fgSectionMap of
Just _ -> ParseFailed $ FieldShouldBeStanza name line
Nothing -> do
warning $
"Unrecognized field '"
++ name
++ "' on line "
++ show line
return a
setField a (Section line name param fields) =
case Left <$> Map.lookup name sectionMap <|> Right <$> Map.lookup name fgSectionMap of
Just (Left (SectionDescr _ fieldDescrs' sectionDescrs' _ set sectionEmpty)) -> do
Expand Down
5 changes: 5 additions & 0 deletions cabal-install/src/Distribution/Deprecated/ParseUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,7 @@ data PError
= AmbiguousParse String LineNo
| NoParse String LineNo
| TabsError LineNo
| FieldShouldBeStanza String LineNo
| FromString String (Maybe LineNo)
deriving (Eq, Show)

Expand Down Expand Up @@ -186,6 +187,10 @@ locatedErrorMsg (NoParse f n) =
, "Parse of field '" ++ f ++ "' failed."
)
locatedErrorMsg (TabsError n) = (Just n, "Tab used as indentation.")
locatedErrorMsg (FieldShouldBeStanza name lineNumber) =
( Just lineNumber
, "'" ++ name ++ "' is a stanza, not a field. Remove the trailing ':' to parse a stanza."
)
locatedErrorMsg (FromString s n) = (n, s)

syntaxError :: LineNo -> String -> ParseResult a
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
# cabal build
Error: [Cabal-7090]
Error parsing project file <ROOT>/cabal.project:4:
'source-repository-package' is a stanza, not a field. Remove the trailing ':' to parse a stanza.
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
packages: .

-- This is an error; a trailing `:` is syntax for a field, not a stanza!
source-repository-package:
type: git
location: https://github.com/haskell-hvr/Only
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
import Test.Cabal.Prelude

main = cabalTest $ do
result <- fails $ cabal' "build" []
assertOutputContains "Error parsing project file" result
assertOutputContains "'source-repository-package' is a stanza, not a field." result
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module MyLib (someFunc) where

someFunc :: IO ()
someFunc = putStrLn "someFunc"
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
cabal-version: 3.0
name: test
version: 0.1.0.0
license: NONE
author: [email protected]
maintainer: Rebecca Turner
build-type: Simple

library
exposed-modules: MyLib
build-depends: base
hs-source-dirs: src
default-language: Haskell2010

0 comments on commit f34aba9

Please sign in to comment.