1
1
{-# LANGUAGE ConstraintKinds #-}
2
2
{-# LANGUAGE DataKinds #-}
3
3
{-# LANGUAGE DeriveGeneric #-}
4
+ {-# LANGUAGE LambdaCase #-}
4
5
{-# LANGUAGE NamedFieldPuns #-}
5
6
{-# LANGUAGE RecordWildCards #-}
6
7
{-# LANGUAGE ScopedTypeVariables #-}
8
+ {-# LANGUAGE TupleSections #-}
7
9
{-# LANGUAGE ViewPatterns #-}
8
10
9
11
-- | Project configuration, implementation in terms of legacy types.
@@ -161,6 +163,11 @@ import Distribution.Deprecated.ParseUtils
161
163
, syntaxError
162
164
)
163
165
import qualified Distribution.Deprecated.ParseUtils as ParseUtils
166
+ import Distribution.Deprecated.ProjectParseUtils
167
+ ( ProjectParseResult (.. )
168
+ , projectParse
169
+ , projectParseFail
170
+ )
164
171
import Distribution.Deprecated.ReadP
165
172
( ReadP
166
173
, (+++)
@@ -185,6 +192,7 @@ import Distribution.Utils.Path hiding
185
192
)
186
193
187
194
import qualified Data.ByteString.Char8 as BS
195
+ import Data.Functor ((<&>) )
188
196
import qualified Data.Map as Map
189
197
import qualified Data.Set as Set
190
198
import Network.URI (URI (.. ), nullURIAuth , parseURI )
@@ -242,12 +250,15 @@ parseProject
242
250
-> Verbosity
243
251
-> ProjectConfigToParse
244
252
-- ^ 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
251
262
252
263
parseProjectSkeleton
253
264
:: FilePath
@@ -259,60 +270,65 @@ parseProjectSkeleton
259
270
-- ^ The path of the file being parsed, either the root or an import
260
271
-> ProjectConfigToParse
261
272
-- ^ The contents of the file to parse
262
- -> IO (ParseResult ProjectConfigSkeleton )
273
+ -> IO (ProjectParseResult ProjectConfigSkeleton )
263
274
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)
265
276
where
266
- go :: [ParseUtils. Field ] -> [ParseUtils. Field ] -> IO (ParseResult ProjectConfigSkeleton )
277
+ go :: [ParseUtils. Field ] -> [ParseUtils. Field ] -> IO (ProjectParseResult ProjectConfigSkeleton )
267
278
go acc (x : xs) = case x of
268
279
(ParseUtils. F _ " import" importLoc) -> do
269
280
let importLocPath = importLoc `consProjectConfigPath` source
270
281
271
282
-- Once we canonicalize the import path, we can check for cyclical imports
283
+ normSource <- canonicalizeConfigPath projectDir source
272
284
normLocPath <- canonicalizeConfigPath projectDir importLocPath
273
-
274
285
debug verbosity $ " \n import path, normalized\n =======================\n " ++ render (docProjectConfigPath normLocPath)
275
286
276
287
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
278
289
else do
279
290
when
280
291
(isUntrimmedUriConfigPath importLocPath)
281
292
(noticeDoc verbosity $ untrimmedUriImportMsg (Disp. text " Warning:" ) importLocPath)
282
- normSource <- canonicalizeConfigPath projectDir source
283
293
let fs = (\ z -> CondNode z [normLocPath] mempty ) <$> fieldsToConfig normSource (reverse acc)
284
294
res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
285
295
rest <- go [] xs
286
- pure . fmap mconcat . sequence $ [fs, res, rest]
296
+ pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
287
297
(ParseUtils. Section l " if" p xs') -> do
298
+ normSource <- canonicalizeConfigPath projectDir source
288
299
subpcs <- go [] xs'
289
300
let fs = singletonProjectConfigSkeleton <$> fieldsToConfig source (reverse acc)
290
301
(elseClauses, rest) <- parseElseClauses xs
291
302
let condNode =
292
303
(\ c pcs e -> CondNode mempty mempty [CondBranch c pcs e])
293
304
<$>
294
305
-- 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
+ )
296
309
<*> subpcs
297
310
<*> elseClauses
298
- pure . fmap mconcat . sequence $ [fs, condNode, rest]
311
+ pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, condNode, rest]
299
312
_ -> go (x : acc) xs
300
313
go acc [] = do
301
314
normSource <- canonicalizeConfigPath projectDir source
302
- pure . fmap singletonProjectConfigSkeleton . fieldsToConfig normSource $ reverse acc
315
+ pure . fmap singletonProjectConfigSkeleton . projectParse Nothing normSource . fieldsToConfig normSource $ reverse acc
303
316
304
- parseElseClauses :: [ParseUtils. Field ] -> IO (ParseResult (Maybe ProjectConfigSkeleton ), ParseResult ProjectConfigSkeleton )
317
+ parseElseClauses :: [ParseUtils. Field ] -> IO (ProjectParseResult (Maybe ProjectConfigSkeleton ), ProjectParseResult ProjectConfigSkeleton )
305
318
parseElseClauses x = case x of
306
319
(ParseUtils. Section _l " else" _p xs' : xs) -> do
307
320
subpcs <- go [] xs'
308
321
rest <- go [] xs
309
322
pure (Just <$> subpcs, rest)
310
323
(ParseUtils. Section l " elif" p xs' : xs) -> do
324
+ normSource <- canonicalizeConfigPath projectDir source
311
325
subpcs <- go [] xs'
312
326
(elseClauses, rest) <- parseElseClauses xs
313
327
let condNode =
314
328
(\ 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
+ )
316
332
<*> subpcs
317
333
<*> elseClauses
318
334
pure (Just <$> condNode, rest)
@@ -331,15 +347,16 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project
331
347
addProvenance :: ProjectConfigPath -> ProjectConfig -> ProjectConfig
332
348
addProvenance sourcePath x = x{projectConfigProvenance = Set. singleton $ Explicit sourcePath}
333
349
350
+ adaptParseError :: Show e => ParseUtils. LineNo -> Either e a -> ParseResult a
334
351
adaptParseError _ (Right x) = pure x
335
352
adaptParseError l (Left e) = parseFail $ ParseUtils. FromString (show e) (Just l)
336
353
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
339
356
where
340
- addWarnings (ParseOk ws' x') = ParseOk (ws' ++ ws ) x'
357
+ addWarnings (ProjectParseOk ws' x') = ProjectParseOk (ws' ++ ((p,) <$> ws) ) x'
341
358
addWarnings x' = x'
342
- liftPR _ (ParseFailed e) = pure $ ParseFailed e
359
+ liftPR p _ (ParseFailed e) = pure $ projectParseFail Nothing ( Just p) e
343
360
344
361
fetchImportConfig :: ProjectConfigPath -> IO BS. ByteString
345
362
fetchImportConfig (ProjectConfigPath (pci :| _)) = do
@@ -362,12 +379,14 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project
362
379
where
363
380
isSet f = f (projectConfigShared pc) /= NoFlag
364
381
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
369
388
370
- sanityWalkBranch :: CondBranch ConfVar [ProjectConfigPath ] ProjectConfig -> ParseResult ()
389
+ sanityWalkBranch :: CondBranch ConfVar [ProjectConfigPath ] ProjectConfig -> ProjectParseResult ()
371
390
sanityWalkBranch (CondBranch _c t f) = traverse_ (sanityWalkPCS True ) f >> sanityWalkPCS True t >> pure ()
372
391
373
392
------------------------------------------------------------------
0 commit comments