Skip to content
Snippets Groups Projects
Commit 3e17cec9 authored by Oleg Grenrus's avatar Oleg Grenrus Committed by f-a
Browse files

Make readFields warn about inconsistent indentation.

This is affect of using indentOfAtLeast method:
any indentation greater than current offset is fine.

That behavior is desirable to parsing multiline field contents,
but it is a bit surprising for fields, which we expect to be aligned.

Such insonsistency seems to be always a mistake, and it's easy to fix once
a machine points it out.
parent aaab541e
No related branches found
No related tags found
No related merge requests found
...@@ -31,7 +31,7 @@ module Distribution.Fields.LexerMonad ...@@ -31,7 +31,7 @@ module Distribution.Fields.LexerMonad
import qualified Data.ByteString as B import qualified Data.ByteString as B
import qualified Data.List.NonEmpty as NE import qualified Data.List.NonEmpty as NE
import Distribution.Compat.Prelude import Distribution.Compat.Prelude
import Distribution.Parsec.Position (Position (..), showPos) import Distribution.Parsec.Position (Position (..), positionRow, showPos)
import Distribution.Parsec.Warning (PWarnType (..), PWarning (..)) import Distribution.Parsec.Warning (PWarnType (..), PWarning (..))
import Prelude () import Prelude ()
...@@ -67,6 +67,8 @@ data LexWarningType ...@@ -67,6 +67,8 @@ data LexWarningType
LexWarningBOM LexWarningBOM
| -- | Leading tags | -- | Leading tags
LexWarningTab LexWarningTab
| -- | indentation decreases
LexInconsistentIndentation
deriving (Eq, Ord, Show) deriving (Eq, Ord, Show)
data LexWarning data LexWarning
...@@ -79,7 +81,7 @@ toPWarnings :: [LexWarning] -> [PWarning] ...@@ -79,7 +81,7 @@ toPWarnings :: [LexWarning] -> [PWarning]
toPWarnings = toPWarnings =
map (uncurry toWarning) map (uncurry toWarning)
. Map.toList . Map.toList
. Map.fromListWith (<>) . Map.fromListWith (flip (<>)) -- fromListWith gives existing element first.
. map (\(LexWarning t p) -> (t, pure p)) . map (\(LexWarning t p) -> (t, pure p))
where where
toWarning LexWarningBOM poss = toWarning LexWarningBOM poss =
...@@ -88,6 +90,8 @@ toPWarnings = ...@@ -88,6 +90,8 @@ toPWarnings =
PWarning PWTLexNBSP (NE.head poss) $ "Non breaking spaces at " ++ intercalate ", " (NE.toList $ fmap showPos poss) PWarning PWTLexNBSP (NE.head poss) $ "Non breaking spaces at " ++ intercalate ", " (NE.toList $ fmap showPos poss)
toWarning LexWarningTab poss = toWarning LexWarningTab poss =
PWarning PWTLexTab (NE.head poss) $ "Tabs used as indentation at " ++ intercalate ", " (NE.toList $ fmap showPos poss) 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)
{- FOURMOLU_DISABLE -} {- FOURMOLU_DISABLE -}
data LexState = LexState data LexState = LexState
......
...@@ -42,9 +42,10 @@ import Distribution.Fields.LexerMonad ...@@ -42,9 +42,10 @@ import Distribution.Fields.LexerMonad
( LexResult (..) ( LexResult (..)
, LexState (..) , LexState (..)
, LexWarning (..) , LexWarning (..)
, LexWarningType (..)
, unLex , unLex
) )
import Distribution.Parsec.Position (Position (..)) import Distribution.Parsec.Position (Position (..), positionCol)
import Text.Parsec.Combinator hiding (eof, notFollowedBy) import Text.Parsec.Combinator hiding (eof, notFollowedBy)
import Text.Parsec.Error import Text.Parsec.Error
import Text.Parsec.Pos import Text.Parsec.Pos
...@@ -340,11 +341,36 @@ readFields' s = do ...@@ -340,11 +341,36 @@ readFields' s = do
where where
parser = do parser = do
fields <- cabalStyleFile fields <- cabalStyleFile
ws <- getLexerWarnings ws <- getLexerWarnings -- lexer accumulates warnings in reverse (consing them to the list)
pure (fields, ws) pure (fields, reverse ws ++ checkIndentation fields [])
lexSt = mkLexState' (mkLexState s) lexSt = mkLexState' (mkLexState s)
-- | Check (recursively) that all fields inside a block are indented the same.
--
-- We have to do this as a post-processing check.
-- As the parser uses indentOfAtLeast approach, we don't know what is the "correct"
-- indentation for following fields.
--
-- To catch during parsing we would need to parse first field/section of a section
-- and then parse the following ones (softly) requiring the exactly the same indentation.
checkIndentation :: [Field Position] -> [LexWarning] -> [LexWarning]
checkIndentation [] = id
checkIndentation (Field name _ : fs') = checkIndentation' (nameAnn name) fs'
checkIndentation (Section name _ fs : fs') = checkIndentation fs . checkIndentation' (nameAnn name) fs'
-- | We compare adjacent fields to reduce the amount of reported indentation warnings.
checkIndentation' :: Position -> [Field Position] -> [LexWarning] -> [LexWarning]
checkIndentation' _ [] = id
checkIndentation' pos (Field name _ : fs') = checkIndentation'' pos (nameAnn name) . checkIndentation' (nameAnn name) fs'
checkIndentation' pos (Section name _ fs : fs') = checkIndentation'' pos (nameAnn name) . checkIndentation fs . checkIndentation' (nameAnn name) fs'
-- | Check that positions' columns are the same.
checkIndentation'' :: Position -> Position -> [LexWarning] -> [LexWarning]
checkIndentation'' a b
| positionCol a == positionCol b = id
| otherwise = (LexWarning LexInconsistentIndentation b :)
#ifdef CABAL_PARSEC_DEBUG #ifdef CABAL_PARSEC_DEBUG
parseTest' :: Show a => Parsec LexState' () a -> SourceName -> B8.ByteString -> IO () parseTest' :: Show a => Parsec LexState' () a -> SourceName -> B8.ByteString -> IO ()
parseTest' p fname s = parseTest' p fname s =
......
...@@ -57,6 +57,8 @@ data PWarnType ...@@ -57,6 +57,8 @@ data PWarnType
PWTSpecVersion PWTSpecVersion
| -- | Empty filepath, i.e. literally "" | -- | Empty filepath, i.e. literally ""
PWTEmptyFilePath PWTEmptyFilePath
| -- | sections contents (sections and fields) are indented inconsistently
PWTInconsistentIndentation
| -- | Experimental feature | -- | Experimental feature
PWTExperimental PWTExperimental
deriving (Eq, Ord, Show, Enum, Bounded, Generic) deriving (Eq, Ord, Show, Enum, Bounded, Generic)
......
...@@ -57,6 +57,7 @@ checkTests = testGroup "regressions" ...@@ -57,6 +57,7 @@ checkTests = testGroup "regressions"
, checkTest "issue-7776-b.cabal" , checkTest "issue-7776-b.cabal"
, checkTest "issue-7776-c.cabal" , checkTest "issue-7776-c.cabal"
, checkTest "issue-8646.cabal" , checkTest "issue-8646.cabal"
, checkTest "decreasing-indentation.cabal"
] ]
checkTest :: FilePath -> TestTree checkTest :: FilePath -> TestTree
......
name: RSA
category: Cryptography, Codec
version: 1.0.0
license: BSD3
license-file: LICENSE
author: Adam Wick <awick@galois.com>
maintainer: Adam Wick <awick@galois.com>
stability: stable
build-type: Simple
cabal-version: >= 1.2
tested-with: GHC ==6.8.0
synopsis: Implementation of RSA, using the padding schemes of PKCS#1 v2.1.
description: This library implements the RSA encryption and signature
algorithms for arbitrarily-sized ByteStrings. While the
implementations work, they are not necessarily the fastest ones
on the planet. Particularly key generation. The algorithms
included are based of RFC 3447, or the Public-Key Cryptography
Standard for RSA, version 2.1 (a.k.a, PKCS#1 v2.1).
Flag IncludeMD5
Description: Include support for using MD5 in the various crypto routines.
Flag UseBinary
Description: Use the binary package for serializing keys.
Library
build-depends: base >= 3
if flag(UseBinary)
build-depends: binary <10
CPP-Options: -DUSE_BINARY
if flag(IncludeMD5) && flag(UseBinary)
build-depends: pureMD5 <10
CPP-Options: -DINCLUDE_MD5
exposed-modules: Codec.Crypto.RSA
Executable test_rsa
build-depends: base >= 3
CPP-Options: -DRSA_TEST
Main-Is: Test.hs
Other-Modules: Codec.Crypto.RSA
-- The above is actual RSA-1.0.0 cabal file (slightly modified to produce less check warnings)
-- The following sections is further inconsistent indentation examples.
-- Note that here main-is is part of GHC-Options field. (and thus warned about as missing)
Executable warnings
build-depends: base < 5
GHC-Options: -Wall
main-is: warnings.hs
Other-Modules: FooBar
-- Increasing indentation is also possible if we use braces to delimit field contents.
Executable warnings2
build-depends: { base <5 }
main-is: { warnings2.hs }
Other-Modules: FooBar
-- another common mistake is something like below,
-- where a sub-section is over-indented
flag splitBase
Executable warnings3
if flag(splitBase)
build-depends: base >= 3
else
build-depends: base < 3
Main-Is: warnings3.hs
Other-Modules:
Graphics.UI.WXCore
Graphics.UI.WXCore.Wx
decreasing-indentation.cabal:38:3: Inconsistent indentation. Indentation jumps at lines 38, 49, 56, 57, 69
No 'main-is' field found for executable warnings
...@@ -16,4 +16,4 @@ library ...@@ -16,4 +16,4 @@ library
-- if !os(linux) -- if !os(linux)
-- exposed-modules: Bar -- exposed-modules: Bar
default-language: Haskell2010 default-language: Haskell2010
synopsis: Warn about inconsistent indentation
packages: Cabal-syntax
prs: #8975
description:
Make Cabal warn about inconsistent indentation in .cabal files.
For example warn about somewhat common decreasing indentation like in
```cabal
library
default-language: Haskell2010
build-depends: base
ghc-options: -Wall
```
The change is `readFields` function.
This is an effect of using `indentOfAtLeast` method/approach: any indentation greater than current offset is accepted.
That behavior is desirable to parsing multiline field contents, but it is a bit surprising for fields in sections, which we expect to be aligned.
Such insonsistency seems to be always a mistake, and it's easy to fix once a machine points it out.
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment