Skip to content

Commit bf432d2

Browse files
authored
Merge pull request #10644 from cabalism/fix/import-parse-error-location
Add source file to project parse errors and warnings
2 parents 54d364d + 8ba44d3 commit bf432d2

File tree

26 files changed

+727
-109
lines changed

26 files changed

+727
-109
lines changed

cabal-install/cabal-install.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -86,6 +86,7 @@ library
8686
-- this modules are moved from Cabal
8787
-- they are needed for as long until cabal-install moves to parsec parser
8888
Distribution.Deprecated.ParseUtils
89+
Distribution.Deprecated.ProjectParseUtils
8990
Distribution.Deprecated.ReadP
9091
Distribution.Deprecated.ViewAsFieldDescr
9192

cabal-install/src/Distribution/Client/Errors.hs

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,8 @@ import Distribution.Pretty
3333
import Distribution.Simple (VersionRange)
3434
import Distribution.Simple.Utils
3535
import Network.URI
36+
import Text.PrettyPrint hiding (render, (<>))
37+
import qualified Text.PrettyPrint as PP
3638
import Text.Regex.Posix.ByteString (WrapError)
3739

3840
data CabalInstallException
@@ -112,7 +114,7 @@ data CabalInstallException
112114
| ParseExtraLinesFailedErr String String
113115
| ParseExtraLinesOkError [PWarning]
114116
| FetchPackageErr
115-
| ReportParseResult String FilePath String String
117+
| ReportParseResult String FilePath String Doc
116118
| ReportSourceRepoProblems String
117119
| BenchActionException
118120
| RenderBenchTargetProblem [String]
@@ -495,13 +497,12 @@ exceptionMessageCabalInstall e = case e of
495497
ParseExtraLinesOkError ws -> unlines (map (showPWarning "Error parsing additional config lines") ws)
496498
FetchPackageErr -> "fetchPackage: source repos not supported"
497499
ReportParseResult filetype filename line msg ->
498-
"Error parsing "
499-
++ filetype
500-
++ " "
501-
++ filename
502-
++ line
503-
++ ":\n"
504-
++ msg
500+
PP.render $
501+
vcat
502+
-- NOTE: As given to us, the line number string is prefixed by a colon.
503+
[ text "Error parsing" <+> text filetype <+> text filename PP.<> text line PP.<> colon
504+
, nest 1 $ text "-" <+> msg
505+
]
505506
ReportSourceRepoProblems errorStr -> errorStr
506507
BenchActionException ->
507508
"The bench command does not support '--only-dependencies'. "

cabal-install/src/Distribution/Client/ProjectConfig.hs

Lines changed: 53 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -66,8 +66,18 @@ module Distribution.Client.ProjectConfig
6666
, maxNumFetchJobs
6767
) where
6868

69-
import Distribution.Client.Compat.Prelude
70-
import Text.PrettyPrint (nest, render, text, vcat)
69+
import Distribution.Client.Compat.Prelude hiding (empty)
70+
import Distribution.Simple.Utils
71+
( createDirectoryIfMissingVerbose
72+
, dieWithException
73+
, maybeExit
74+
, notice
75+
, noticeDoc
76+
, ordNub
77+
, rawSystemIOWithEnv
78+
, warn
79+
)
80+
import Text.PrettyPrint (cat, colon, comma, empty, hsep, nest, quotes, render, text, vcat)
7181
import Prelude ()
7282

7383
import Distribution.Client.Glob
@@ -136,10 +146,12 @@ import Distribution.Client.Utils
136146
( determineNumJobs
137147
)
138148
import qualified Distribution.Deprecated.ParseUtils as OldParser
139-
( ParseResult (..)
140-
, locatedErrorMsg
149+
( locatedErrorMsg
141150
, showPWarning
142151
)
152+
import qualified Distribution.Deprecated.ProjectParseUtils as OldParser
153+
( ProjectParseResult (..)
154+
)
143155
import Distribution.Fields
144156
( PError
145157
, PWarning
@@ -172,14 +184,6 @@ import Distribution.Simple.Setup
172184
, fromFlagOrDefault
173185
, toFlag
174186
)
175-
import Distribution.Simple.Utils
176-
( createDirectoryIfMissingVerbose
177-
, dieWithException
178-
, maybeExit
179-
, notice
180-
, rawSystemIOWithEnv
181-
, warn
182-
)
183187
import Distribution.System
184188
( Platform
185189
)
@@ -240,6 +244,7 @@ import System.IO
240244
, withBinaryFile
241245
)
242246

247+
import Distribution.Deprecated.ProjectParseUtils (ProjectParseError (..), ProjectParseWarning)
243248
import Distribution.Solver.Types.ProjectConfigPath
244249

245250
----------------------------------------
@@ -874,16 +879,45 @@ readGlobalConfig verbosity configFileFlag = do
874879
monitorFiles [monitorFileHashed configFile]
875880
return (convertLegacyGlobalConfig config)
876881

877-
reportParseResult :: Verbosity -> String -> FilePath -> OldParser.ParseResult ProjectConfigSkeleton -> IO ProjectConfigSkeleton
878-
reportParseResult verbosity _filetype filename (OldParser.ParseOk warnings x) = do
882+
reportProjectParseWarnings :: Verbosity -> FilePath -> [ProjectParseWarning] -> IO ()
883+
reportProjectParseWarnings verbosity projectFile warnings =
879884
unless (null warnings) $
880-
let msg = unlines (map (OldParser.showPWarning (intercalate ", " $ filename : (projectConfigPathRoot <$> projectSkeletonImports x))) warnings)
881-
in warn verbosity msg
885+
let msgs =
886+
[ OldParser.showPWarning pFilename w
887+
| (p, w) <- warnings
888+
, let pFilename = fst $ unconsProjectConfigPath p
889+
]
890+
in noticeDoc verbosity $
891+
vcat
892+
[ (text "Warnings found while parsing the project file" <> comma) <+> (text (takeFileName projectFile) <> colon)
893+
, cat [nest 1 $ text "-" <+> text m | m <- ordNub msgs]
894+
]
895+
896+
reportParseResult :: Verbosity -> String -> FilePath -> OldParser.ProjectParseResult ProjectConfigSkeleton -> IO ProjectConfigSkeleton
897+
reportParseResult verbosity _filetype projectFile (OldParser.ProjectParseOk warnings x) = do
898+
reportProjectParseWarnings verbosity projectFile warnings
882899
return x
883-
reportParseResult verbosity filetype filename (OldParser.ParseFailed err) =
900+
reportParseResult verbosity filetype projectFile (OldParser.ProjectParseFailed (ProjectParseError snippet rootOrImportee err)) = do
884901
let (line, msg) = OldParser.locatedErrorMsg err
885-
errLineNo = maybe "" (\n -> ':' : show n) line
886-
in dieWithException verbosity $ ReportParseResult filetype filename errLineNo msg
902+
let errLineNo = maybe "" (\n -> ':' : show n) line
903+
let (sourceFile, provenance) =
904+
maybe
905+
(projectFile, empty)
906+
( \p ->
907+
( fst $ unconsProjectConfigPath p
908+
, if isTopLevelConfigPath p then empty else docProjectConfigPath p
909+
)
910+
)
911+
rootOrImportee
912+
let doc = case snippet of
913+
Nothing -> vcat (text <$> lines msg)
914+
Just s ->
915+
vcat
916+
[ provenance
917+
, text "Failed to parse" <+> quotes (text s) <+> (text "with error" <> colon)
918+
, nest 2 $ hsep $ text <$> lines msg
919+
]
920+
dieWithException verbosity $ ReportParseResult filetype sourceFile errLineNo doc
887921

888922
---------------------------------------------
889923
-- Finding packages in the project

cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs

Lines changed: 46 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
11
{-# LANGUAGE ConstraintKinds #-}
22
{-# LANGUAGE DataKinds #-}
33
{-# LANGUAGE DeriveGeneric #-}
4+
{-# LANGUAGE LambdaCase #-}
45
{-# LANGUAGE NamedFieldPuns #-}
56
{-# LANGUAGE RecordWildCards #-}
67
{-# LANGUAGE ScopedTypeVariables #-}
8+
{-# LANGUAGE TupleSections #-}
79
{-# LANGUAGE ViewPatterns #-}
810

911
-- | Project configuration, implementation in terms of legacy types.
@@ -161,6 +163,11 @@ import Distribution.Deprecated.ParseUtils
161163
, syntaxError
162164
)
163165
import qualified Distribution.Deprecated.ParseUtils as ParseUtils
166+
import Distribution.Deprecated.ProjectParseUtils
167+
( ProjectParseResult (..)
168+
, projectParse
169+
, projectParseFail
170+
)
164171
import Distribution.Deprecated.ReadP
165172
( ReadP
166173
, (+++)
@@ -185,6 +192,7 @@ import Distribution.Utils.Path hiding
185192
)
186193

187194
import qualified Data.ByteString.Char8 as BS
195+
import Data.Functor ((<&>))
188196
import qualified Data.Map as Map
189197
import qualified Data.Set as Set
190198
import Network.URI (URI (..), nullURIAuth, parseURI)
@@ -242,12 +250,15 @@ parseProject
242250
-> Verbosity
243251
-> ProjectConfigToParse
244252
-- ^ The contents of the file to parse
245-
-> IO (ParseResult ProjectConfigSkeleton)
246-
parseProject rootPath cacheDir httpTransport verbosity configToParse = do
247-
let (dir, projectFileName) = splitFileName rootPath
248-
projectDir <- makeAbsolute dir
249-
projectPath <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
250-
parseProjectSkeleton cacheDir httpTransport verbosity projectDir projectPath configToParse
253+
-> IO (ProjectParseResult ProjectConfigSkeleton)
254+
parseProject rootPath cacheDir httpTransport verbosity configToParse =
255+
do
256+
let (dir, projectFileName) = splitFileName rootPath
257+
projectDir <- makeAbsolute dir
258+
projectPath <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
259+
parseProjectSkeleton cacheDir httpTransport verbosity projectDir projectPath configToParse
260+
-- NOTE: Reverse the warnings so they are in line number order.
261+
<&> \case ProjectParseOk ws x -> ProjectParseOk (reverse ws) x; x -> x
251262

252263
parseProjectSkeleton
253264
:: FilePath
@@ -259,60 +270,65 @@ parseProjectSkeleton
259270
-- ^ The path of the file being parsed, either the root or an import
260271
-> ProjectConfigToParse
261272
-- ^ The contents of the file to parse
262-
-> IO (ParseResult ProjectConfigSkeleton)
273+
-> IO (ProjectParseResult ProjectConfigSkeleton)
263274
parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
264-
(sanityWalkPCS False =<<) <$> liftPR (go []) (ParseUtils.readFields bs)
275+
(sanityWalkPCS False =<<) <$> liftPR source (go []) (ParseUtils.readFields bs)
265276
where
266-
go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ParseResult ProjectConfigSkeleton)
277+
go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ProjectParseResult ProjectConfigSkeleton)
267278
go acc (x : xs) = case x of
268279
(ParseUtils.F _ "import" importLoc) -> do
269280
let importLocPath = importLoc `consProjectConfigPath` source
270281

271282
-- Once we canonicalize the import path, we can check for cyclical imports
283+
normSource <- canonicalizeConfigPath projectDir source
272284
normLocPath <- canonicalizeConfigPath projectDir importLocPath
273-
274285
debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath)
275286

276287
if isCyclicConfigPath normLocPath
277-
then pure . parseFail $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
288+
then pure . projectParseFail Nothing (Just normSource) $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
278289
else do
279290
when
280291
(isUntrimmedUriConfigPath importLocPath)
281292
(noticeDoc verbosity $ untrimmedUriImportMsg (Disp.text "Warning:") importLocPath)
282-
normSource <- canonicalizeConfigPath projectDir source
283293
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
284294
res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
285295
rest <- go [] xs
286-
pure . fmap mconcat . sequence $ [fs, res, rest]
296+
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
287297
(ParseUtils.Section l "if" p xs') -> do
298+
normSource <- canonicalizeConfigPath projectDir source
288299
subpcs <- go [] xs'
289300
let fs = singletonProjectConfigSkeleton <$> fieldsToConfig source (reverse acc)
290301
(elseClauses, rest) <- parseElseClauses xs
291302
let condNode =
292303
(\c pcs e -> CondNode mempty mempty [CondBranch c pcs e])
293304
<$>
294305
-- we rewrap as as a section so the readFields lexer of the conditional parser doesn't get confused
295-
adaptParseError l (parseConditionConfVarFromClause . BS.pack $ "if(" <> p <> ")")
306+
( let s = "if(" <> p <> ")"
307+
in projectParse (Just s) normSource (adaptParseError l (parseConditionConfVarFromClause $ BS.pack s))
308+
)
296309
<*> subpcs
297310
<*> elseClauses
298-
pure . fmap mconcat . sequence $ [fs, condNode, rest]
311+
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, condNode, rest]
299312
_ -> go (x : acc) xs
300313
go acc [] = do
301314
normSource <- canonicalizeConfigPath projectDir source
302-
pure . fmap singletonProjectConfigSkeleton . fieldsToConfig normSource $ reverse acc
315+
pure . fmap singletonProjectConfigSkeleton . projectParse Nothing normSource . fieldsToConfig normSource $ reverse acc
303316

304-
parseElseClauses :: [ParseUtils.Field] -> IO (ParseResult (Maybe ProjectConfigSkeleton), ParseResult ProjectConfigSkeleton)
317+
parseElseClauses :: [ParseUtils.Field] -> IO (ProjectParseResult (Maybe ProjectConfigSkeleton), ProjectParseResult ProjectConfigSkeleton)
305318
parseElseClauses x = case x of
306319
(ParseUtils.Section _l "else" _p xs' : xs) -> do
307320
subpcs <- go [] xs'
308321
rest <- go [] xs
309322
pure (Just <$> subpcs, rest)
310323
(ParseUtils.Section l "elif" p xs' : xs) -> do
324+
normSource <- canonicalizeConfigPath projectDir source
311325
subpcs <- go [] xs'
312326
(elseClauses, rest) <- parseElseClauses xs
313327
let condNode =
314328
(\c pcs e -> CondNode mempty mempty [CondBranch c pcs e])
315-
<$> adaptParseError l (parseConditionConfVarFromClause . BS.pack $ "else(" <> p <> ")")
329+
<$> ( let s = "elif(" <> p <> ")"
330+
in projectParse (Just s) normSource (adaptParseError l (parseConditionConfVarFromClause $ BS.pack s))
331+
)
316332
<*> subpcs
317333
<*> elseClauses
318334
pure (Just <$> condNode, rest)
@@ -331,15 +347,16 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project
331347
addProvenance :: ProjectConfigPath -> ProjectConfig -> ProjectConfig
332348
addProvenance sourcePath x = x{projectConfigProvenance = Set.singleton $ Explicit sourcePath}
333349

350+
adaptParseError :: Show e => ParseUtils.LineNo -> Either e a -> ParseResult a
334351
adaptParseError _ (Right x) = pure x
335352
adaptParseError l (Left e) = parseFail $ ParseUtils.FromString (show e) (Just l)
336353

337-
liftPR :: (a -> IO (ParseResult b)) -> ParseResult a -> IO (ParseResult b)
338-
liftPR f (ParseOk ws x) = addWarnings <$> f x
354+
liftPR :: ProjectConfigPath -> (a -> IO (ProjectParseResult b)) -> ParseResult a -> IO (ProjectParseResult b)
355+
liftPR p f (ParseOk ws x) = addWarnings <$> f x
339356
where
340-
addWarnings (ParseOk ws' x') = ParseOk (ws' ++ ws) x'
357+
addWarnings (ProjectParseOk ws' x') = ProjectParseOk (ws' ++ ((p,) <$> ws)) x'
341358
addWarnings x' = x'
342-
liftPR _ (ParseFailed e) = pure $ ParseFailed e
359+
liftPR p _ (ParseFailed e) = pure $ projectParseFail Nothing (Just p) e
343360

344361
fetchImportConfig :: ProjectConfigPath -> IO BS.ByteString
345362
fetchImportConfig (ProjectConfigPath (pci :| _)) = do
@@ -362,12 +379,14 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project
362379
where
363380
isSet f = f (projectConfigShared pc) /= NoFlag
364381

365-
sanityWalkPCS :: Bool -> ProjectConfigSkeleton -> ParseResult ProjectConfigSkeleton
366-
sanityWalkPCS underConditional t@(CondNode d _c comps)
367-
| underConditional && modifiesCompiler d = parseFail $ ParseUtils.FromString "Cannot set compiler in a conditional clause of a cabal project file" Nothing
368-
| otherwise = mapM_ sanityWalkBranch comps >> pure t
382+
sanityWalkPCS :: Bool -> ProjectConfigSkeleton -> ProjectParseResult ProjectConfigSkeleton
383+
sanityWalkPCS underConditional t@(CondNode d (listToMaybe -> c) comps)
384+
| underConditional && modifiesCompiler d =
385+
projectParseFail Nothing c $ ParseUtils.FromString "Cannot set compiler in a conditional clause of a cabal project file" Nothing
386+
| otherwise =
387+
mapM_ sanityWalkBranch comps >> pure t
369388

370-
sanityWalkBranch :: CondBranch ConfVar [ProjectConfigPath] ProjectConfig -> ParseResult ()
389+
sanityWalkBranch :: CondBranch ConfVar [ProjectConfigPath] ProjectConfig -> ProjectParseResult ()
371390
sanityWalkBranch (CondBranch _c t f) = traverse_ (sanityWalkPCS True) f >> sanityWalkPCS True t >> pure ()
372391

373392
------------------------------------------------------------------
Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,51 @@
1+
{-# OPTIONS_HADDOCK hide #-}
2+
3+
module Distribution.Deprecated.ProjectParseUtils
4+
( ProjectParseError (..)
5+
, ProjectParseWarning
6+
, ProjectParseResult (..)
7+
, projectParseFail
8+
, projectParse
9+
) where
10+
11+
import Distribution.Client.Compat.Prelude hiding (get)
12+
import Prelude ()
13+
14+
import qualified Distribution.Deprecated.ParseUtils as Pkg (PError, PWarning, ParseResult (..))
15+
import Distribution.Solver.Types.ProjectConfigPath (ProjectConfigPath)
16+
17+
type ProjectParseWarning = (ProjectConfigPath, Pkg.PWarning)
18+
19+
data ProjectParseError = ProjectParseError
20+
{ projectParseSnippet :: Maybe String
21+
, projectParseSource :: Maybe ProjectConfigPath
22+
, projectParseError :: Pkg.PError
23+
}
24+
deriving (Show)
25+
26+
data ProjectParseResult a
27+
= ProjectParseFailed ProjectParseError
28+
| ProjectParseOk [ProjectParseWarning] a
29+
deriving (Show)
30+
31+
projectParse :: Maybe String -> ProjectConfigPath -> Pkg.ParseResult a -> ProjectParseResult a
32+
projectParse s path (Pkg.ParseFailed err) = ProjectParseFailed $ ProjectParseError s (Just path) err
33+
projectParse _ path (Pkg.ParseOk ws x) = ProjectParseOk [(path, w) | w <- ws] x
34+
35+
instance Functor ProjectParseResult where
36+
fmap _ (ProjectParseFailed err) = ProjectParseFailed err
37+
fmap f (ProjectParseOk ws x) = ProjectParseOk ws $ f x
38+
39+
instance Applicative ProjectParseResult where
40+
pure = ProjectParseOk []
41+
(<*>) = ap
42+
43+
instance Monad ProjectParseResult where
44+
return = pure
45+
ProjectParseFailed err >>= _ = ProjectParseFailed err
46+
ProjectParseOk ws x >>= f = case f x of
47+
ProjectParseFailed err -> ProjectParseFailed err
48+
ProjectParseOk ws' x' -> ProjectParseOk (ws' ++ ws) x'
49+
50+
projectParseFail :: Maybe String -> Maybe ProjectConfigPath -> Pkg.PError -> ProjectParseResult a
51+
projectParseFail s p e = ProjectParseFailed $ ProjectParseError s p e

0 commit comments

Comments
 (0)