Add “Add default-language” suggestion
[cabal.git] / Cabal / src / Distribution / PackageDescription / Check / Target.hs
bloba610b5875a59f2dcdbc88b3608c3a57a576c0388
1 -- |
2 -- Module : Distribution.PackageDescription.Check.Target
3 -- Copyright : Lennart Kolmodin 2008, Francesco Ariis 2023
4 -- License : BSD3
5 --
6 -- Maintainer : cabal-devel@haskell.org
7 -- Portability : portable
8 --
9 -- Fully-realised target (library, executable, …) checking functions.
10 module Distribution.PackageDescription.Check.Target
11 ( checkLibrary
12 , checkForeignLib
13 , checkExecutable
14 , checkTestSuite
15 , checkBenchmark
16 ) where
18 import Distribution.Compat.Prelude
19 import Prelude ()
21 import Distribution.CabalSpecVersion
22 import Distribution.Compat.Lens
23 import Distribution.Compiler
24 import Distribution.ModuleName (ModuleName)
25 import Distribution.Package
26 import Distribution.PackageDescription
27 import Distribution.PackageDescription.Check.Common
28 import Distribution.PackageDescription.Check.Monad
29 import Distribution.PackageDescription.Check.Paths
30 import Distribution.Pretty (prettyShow)
31 import Distribution.Simple.BuildPaths
32 ( autogenPackageInfoModuleName
33 , autogenPathsModuleName
35 import Distribution.Simple.Utils hiding (findPackageDesc, notice)
36 import Distribution.Types.PackageName.Magic
37 import Distribution.Utils.Path
38 import Distribution.Version
39 import Language.Haskell.Extension
40 import System.FilePath (takeExtension)
42 import Control.Monad
44 import qualified Distribution.Types.BuildInfo.Lens as L
46 checkLibrary
47 :: Monad m
48 => Bool -- Is this a sublibrary?
49 -> [AssocDep] -- “Inherited” dependencies for PVP checks.
50 -> Library
51 -> CheckM m ()
52 checkLibrary
53 isSub
54 ads
55 lib@( Library
56 libName_
57 _exposedModules_
58 reexportedModules_
59 signatures_
60 _libExposed_
61 _libVisibility_
62 libBuildInfo_
63 ) = do
64 checkP
65 (libName_ == LMainLibName && isSub)
66 (PackageBuildImpossible UnnamedInternal)
67 -- TODO: bogus if a required-signature was passed through.
68 checkP
69 (null (explicitLibModules lib) && null reexportedModules_)
70 (PackageDistSuspiciousWarn (NoModulesExposed libName_))
71 -- TODO parse-caught check, can safely remove.
72 checkSpecVer
73 CabalSpecV2_0
74 (not . null $ signatures_)
75 (PackageDistInexcusable SignaturesCabal2)
76 -- autogen/includes checks.
77 checkP
78 ( not $
79 all
80 (flip elem (explicitLibModules lib))
81 (libModulesAutogen lib)
83 (PackageBuildImpossible AutogenNotExposed)
84 -- check that all autogen-includes appear on includes or
85 -- install-includes.
86 checkP
87 ( not $
88 all
89 (flip elem (allExplicitIncludes lib))
90 (view L.autogenIncludes lib)
92 $ (PackageBuildImpossible AutogenIncludesNotIncluded)
94 -- § Build infos.
95 checkBuildInfo
96 (CETLibrary libName_)
97 (explicitLibModules lib)
98 ads
99 libBuildInfo_
101 -- Feature checks.
102 -- check use of reexported-modules sections
103 checkSpecVer
104 CabalSpecV1_22
105 (not . null $ reexportedModules_)
106 (PackageDistInexcusable CVReexported)
107 where
108 allExplicitIncludes :: L.HasBuildInfo a => a -> [FilePath]
109 allExplicitIncludes x =
110 view L.includes x
111 ++ view L.installIncludes x
113 checkForeignLib :: Monad m => ForeignLib -> CheckM m ()
114 checkForeignLib
115 ( ForeignLib
116 foreignLibName_
117 _foreignLibType_
118 _foreignLibOptions_
119 foreignLibBuildInfo_
120 _foreignLibVersionInfo_
121 _foreignLibVersionLinux_
122 _foreignLibModDefFile_
123 ) = do
124 checkBuildInfo
125 (CETForeignLibrary foreignLibName_)
128 foreignLibBuildInfo_
130 checkExecutable
131 :: Monad m
132 => [AssocDep] -- “Inherited” dependencies for PVP checks.
133 -> Executable
134 -> CheckM m ()
135 checkExecutable
137 exe@( Executable
138 exeName_
139 modulePath_
140 _exeScope_
141 buildInfo_
142 ) = do
143 -- Target type/name (exe).
144 let cet = CETExecutable exeName_
146 -- § Exe specific checks
147 checkP
148 (null modulePath_)
149 (PackageBuildImpossible (NoMainIs exeName_))
150 -- This check does not apply to scripts.
151 pid <- asksCM (pnPackageId . ccNames)
152 checkP
153 ( pid /= fakePackageId
154 && not (null modulePath_)
155 && not (fileExtensionSupportedLanguage $ modulePath_)
157 (PackageBuildImpossible NoHsLhsMain)
159 -- § Features check
160 checkSpecVer
161 CabalSpecV1_18
162 ( fileExtensionSupportedLanguage modulePath_
163 && takeExtension modulePath_ `notElem` [".hs", ".lhs"]
165 (PackageDistInexcusable MainCCabal1_18)
167 -- Alas exeModules ad exeModulesAutogen (exported from
168 -- Distribution.Types.Executable) take `Executable` as a parameter.
169 checkP
170 (not $ all (flip elem (exeModules exe)) (exeModulesAutogen exe))
171 (PackageBuildImpossible $ AutogenNoOther cet)
172 checkP
173 ( not $
175 (flip elem (view L.includes exe))
176 (view L.autogenIncludes exe)
178 (PackageBuildImpossible AutogenIncludesNotIncludedExe)
180 -- § Build info checks.
181 checkBuildInfo cet [] ads buildInfo_
183 checkTestSuite
184 :: Monad m
185 => [AssocDep] -- “Inherited” dependencies for PVP checks.
186 -> TestSuite
187 -> CheckM m ()
188 checkTestSuite
190 ts@( TestSuite
191 testName_
192 testInterface_
193 testBuildInfo_
194 _testCodeGenerators_
195 ) = do
196 -- Target type/name (test).
197 let cet = CETTest testName_
199 -- § TS specific checks.
200 -- TODO caught by the parser, can remove safely
201 case testInterface_ of
202 TestSuiteUnsupported tt@(TestTypeUnknown _ _) ->
203 tellP (PackageBuildWarning $ TestsuiteTypeNotKnown tt)
204 TestSuiteUnsupported tt ->
205 tellP (PackageBuildWarning $ TestsuiteNotSupported tt)
206 _ -> return ()
207 checkP
208 mainIsWrongExt
209 (PackageBuildImpossible NoHsLhsMain)
210 checkP
211 ( not $
213 (flip elem (testModules ts))
214 (testModulesAutogen ts)
216 (PackageBuildImpossible $ AutogenNoOther cet)
217 checkP
218 ( not $
220 (flip elem (view L.includes ts))
221 (view L.autogenIncludes ts)
223 (PackageBuildImpossible AutogenIncludesNotIncludedExe)
225 -- § Feature checks.
226 checkSpecVer
227 CabalSpecV1_18
228 (mainIsNotHsExt && not mainIsWrongExt)
229 (PackageDistInexcusable MainCCabal1_18)
231 -- § Build info checks.
232 checkBuildInfo cet [] ads testBuildInfo_
233 where
234 mainIsWrongExt =
235 case testInterface_ of
236 TestSuiteExeV10 _ f -> not (fileExtensionSupportedLanguage f)
237 _ -> False
239 mainIsNotHsExt =
240 case testInterface_ of
241 TestSuiteExeV10 _ f -> takeExtension f `notElem` [".hs", ".lhs"]
242 _ -> False
244 checkBenchmark
245 :: Monad m
246 => [AssocDep] -- “Inherited” dependencies for PVP checks.
247 -> Benchmark
248 -> CheckM m ()
249 checkBenchmark
251 bm@( Benchmark
252 benchmarkName_
253 benchmarkInterface_
254 benchmarkBuildInfo_
255 ) = do
256 -- Target type/name (benchmark).
257 let cet = CETBenchmark benchmarkName_
259 -- § Interface & bm specific tests.
260 case benchmarkInterface_ of
261 BenchmarkUnsupported tt@(BenchmarkTypeUnknown _ _) ->
262 tellP (PackageBuildWarning $ BenchmarkTypeNotKnown tt)
263 BenchmarkUnsupported tt ->
264 tellP (PackageBuildWarning $ BenchmarkNotSupported tt)
265 _ -> return ()
266 checkP
267 mainIsWrongExt
268 (PackageBuildImpossible NoHsLhsMainBench)
270 checkP
271 ( not $
273 (flip elem (benchmarkModules bm))
274 (benchmarkModulesAutogen bm)
276 (PackageBuildImpossible $ AutogenNoOther cet)
278 checkP
279 ( not $
281 (flip elem (view L.includes bm))
282 (view L.autogenIncludes bm)
284 (PackageBuildImpossible AutogenIncludesNotIncludedExe)
286 -- § BuildInfo checks.
287 checkBuildInfo cet [] ads benchmarkBuildInfo_
288 where
289 -- Cannot abstract with similar function in checkTestSuite,
290 -- they are different.
291 mainIsWrongExt =
292 case benchmarkInterface_ of
293 BenchmarkExeV10 _ f -> takeExtension f `notElem` [".hs", ".lhs"]
294 _ -> False
296 -- ------------------------------------------------------------
297 -- Build info
298 -- ------------------------------------------------------------
300 -- Check a great deal of things in buildInfo.
301 -- With 'checkBuildInfo' we cannot follow the usual “pattern match
302 -- everything” method, for the number of BuildInfo fields (almost 50)
303 -- but more importantly because accessing options, etc. is done
304 -- with functions from 'Distribution.Types.BuildInfo' (e.g. 'hcOptions').
305 -- Duplicating the effort here means risk of diverging definitions for
306 -- little gain (most likely if a field is added to BI, the relevant
307 -- function will be tweaked in Distribution.Types.BuildInfo too).
308 checkBuildInfo
309 :: Monad m
310 => CEType -- Name and type of the target.
311 -> [ModuleName] -- Additional module names which cannot be
312 -- extracted from BuildInfo (mainly: exposed
313 -- library modules).
314 -> [AssocDep] -- Inherited “internal” (main lib, named
315 -- internal libs) dependencies.
316 -> BuildInfo
317 -> CheckM m ()
318 checkBuildInfo cet ams ads bi = do
319 -- For the sake of clarity, we split che checks in various
320 -- (top level) functions, even if we are not actually going
321 -- deeper in the traversal.
323 checkBuildInfoOptions (cet2bit cet) bi
324 checkBuildInfoPathsContent bi
325 checkBuildInfoPathsWellFormedness bi
327 sv <- asksCM ccSpecVersion
328 checkBuildInfoFeatures bi sv
330 checkAutogenModules ams bi
332 -- PVP: we check for base and all other deps.
333 (ids, rds) <-
334 partitionDeps
336 [mkUnqualComponentName "base"]
337 (mergeDependencies $ targetBuildDepends bi)
338 let ick = const (PackageDistInexcusable BaseNoUpperBounds)
339 rck = PackageDistSuspiciousWarn . MissingUpperBounds cet
340 checkPVP ick ids
341 unless
342 (isInternalTarget cet)
343 (checkPVPs rck rds)
345 -- Custom fields well-formedness (ASCII).
346 mapM_ checkCustomField (customFieldsBI bi)
348 -- Content.
349 mapM_ (checkLocalPathExist "extra-lib-dirs") (extraLibDirs bi)
350 mapM_
351 (checkLocalPathExist "extra-lib-dirs-static")
352 (extraLibDirsStatic bi)
353 mapM_
354 (checkLocalPathExist "extra-framework-dirs")
355 (extraFrameworkDirs bi)
356 mapM_ (checkLocalPathExist "include-dirs") (includeDirs bi)
357 mapM_
358 (checkLocalPathExist "hs-source-dirs" . getSymbolicPath)
359 (hsSourceDirs bi)
361 -- Well formedness of BI contents (no `Haskell2015`, no deprecated
362 -- extensions etc).
363 checkBuildInfoPathsContent :: Monad m => BuildInfo -> CheckM m ()
364 checkBuildInfoPathsContent bi = do
365 mapM_ checkLang (allLanguages bi)
366 mapM_ checkExt (allExtensions bi)
367 mapM_ checkIntDep (targetBuildDepends bi)
368 df <- asksCM ccDesugar
369 -- This way we can use the same function for legacy&non exedeps.
370 let ds = buildToolDepends bi ++ catMaybes (map df $ buildTools bi)
371 mapM_ checkBTDep ds
372 where
373 checkLang :: Monad m => Language -> CheckM m ()
374 checkLang (UnknownLanguage n) =
375 tellP (PackageBuildWarning (UnknownLanguages [n]))
376 checkLang _ = return ()
378 checkExt :: Monad m => Extension -> CheckM m ()
379 checkExt (UnknownExtension n)
380 | n `elem` map prettyShow knownLanguages =
381 tellP (PackageBuildWarning (LanguagesAsExtension [n]))
382 | otherwise =
383 tellP (PackageBuildWarning (UnknownExtensions [n]))
384 checkExt n = do
385 let dss = filter (\(a, _) -> a == n) deprecatedExtensions
386 checkP
387 (not . null $ dss)
388 (PackageDistSuspicious $ DeprecatedExtensions dss)
390 checkIntDep :: Monad m => Dependency -> CheckM m ()
391 checkIntDep d@(Dependency name vrange _) = do
392 mpn <-
393 asksCM
394 ( packageNameToUnqualComponentName
395 . pkgName
396 . pnPackageId
397 . ccNames
399 lns <- asksCM (pnSubLibs . ccNames)
400 pVer <- asksCM (pkgVersion . pnPackageId . ccNames)
401 let allLibNs = mpn : lns
402 when
403 ( mpn == packageNameToUnqualComponentName name
404 -- Make sure it is not a library with the
405 -- same name from another package.
406 && packageNameToUnqualComponentName name `elem` allLibNs
408 ( checkP
409 (not $ pVer `withinRange` vrange)
410 (PackageBuildImpossible $ ImpossibleInternalDep [d])
413 checkBTDep :: Monad m => ExeDependency -> CheckM m ()
414 checkBTDep ed@(ExeDependency n name vrange) = do
415 exns <- asksCM (pnExecs . ccNames)
416 pVer <- asksCM (pkgVersion . pnPackageId . ccNames)
417 pNam <- asksCM (pkgName . pnPackageId . ccNames)
418 checkP
419 ( n == pNam
420 && name `notElem` exns -- internal
421 -- not present
423 (PackageBuildImpossible $ MissingInternalExe [ed])
424 when
425 (name `elem` exns)
426 ( checkP
427 (not $ pVer `withinRange` vrange)
428 (PackageBuildImpossible $ ImpossibleInternalExe [ed])
431 -- Paths well-formedness check for BuildInfo.
432 checkBuildInfoPathsWellFormedness :: Monad m => BuildInfo -> CheckM m ()
433 checkBuildInfoPathsWellFormedness bi = do
434 mapM_ (checkPath False "asm-sources" PathKindFile) (asmSources bi)
435 mapM_ (checkPath False "cmm-sources" PathKindFile) (cmmSources bi)
436 mapM_ (checkPath False "c-sources" PathKindFile) (cSources bi)
437 mapM_ (checkPath False "cxx-sources" PathKindFile) (cxxSources bi)
438 mapM_ (checkPath False "js-sources" PathKindFile) (jsSources bi)
439 mapM_
440 (checkPath False "install-includes" PathKindFile)
441 (installIncludes bi)
442 mapM_
443 (checkPath False "hs-source-dirs" PathKindDirectory . getSymbolicPath)
444 (hsSourceDirs bi)
445 -- Possibly absolute paths.
446 mapM_ (checkPath True "includes" PathKindFile) (includes bi)
447 mapM_
448 (checkPath True "include-dirs" PathKindDirectory)
449 (includeDirs bi)
450 mapM_
451 (checkPath True "extra-lib-dirs" PathKindDirectory)
452 (extraLibDirs bi)
453 mapM_
454 (checkPath True "extra-lib-dirs-static" PathKindDirectory)
455 (extraLibDirsStatic bi)
456 mapM_ checkOptionPath (perCompilerFlavorToList $ options bi)
457 where
458 checkOptionPath
459 :: Monad m
460 => (CompilerFlavor, [FilePath])
461 -> CheckM m ()
462 checkOptionPath (GHC, paths) =
463 mapM_
464 ( \path ->
465 checkP
466 (isInsideDist path)
467 (PackageDistInexcusable $ DistPoint Nothing path)
469 paths
470 checkOptionPath _ = return ()
472 -- Checks for features that can be present in BuildInfo only with certain
473 -- CabalSpecVersion.
474 checkBuildInfoFeatures
475 :: Monad m
476 => BuildInfo
477 -> CabalSpecVersion
478 -> CheckM m ()
479 checkBuildInfoFeatures bi sv = do
480 -- Default language can be used only w/ spec ≥ 1.10
481 checkSpecVer
482 CabalSpecV1_10
483 (isJust $ defaultLanguage bi)
484 (PackageBuildWarning CVDefaultLanguage)
485 -- CheckSpecVer sv.
486 checkDefaultLanguage
487 -- Check use of 'extra-framework-dirs' field.
488 checkSpecVer
489 CabalSpecV1_24
490 (not . null $ extraFrameworkDirs bi)
491 (PackageDistSuspiciousWarn CVExtraFrameworkDirs)
492 -- Check use of default-extensions field don't need to do the
493 -- equivalent check for other-extensions.
494 checkSpecVer
495 CabalSpecV1_10
496 (not . null $ defaultExtensions bi)
497 (PackageBuildWarning CVDefaultExtensions)
498 -- Check use of extensions field
499 checkP
500 (sv >= CabalSpecV1_10 && (not . null $ oldExtensions bi))
501 (PackageBuildWarning CVExtensionsDeprecated)
503 -- asm-sources, cmm-sources and friends only w/ spec ≥ 1.10
504 checkCVSources (asmSources bi)
505 checkCVSources (cmmSources bi)
506 checkCVSources (extraBundledLibs bi)
507 checkCVSources (extraLibFlavours bi)
509 -- extra-dynamic-library-flavours requires ≥ 3.0
510 checkSpecVer
511 CabalSpecV3_0
512 (not . null $ extraDynLibFlavours bi)
513 (PackageDistInexcusable $ CVExtraDynamic [extraDynLibFlavours bi])
514 -- virtual-modules requires ≥ 2.2
515 checkSpecVer CabalSpecV2_2 (not . null $ virtualModules bi) $
516 (PackageDistInexcusable CVVirtualModules)
517 -- Check use of thinning and renaming.
518 checkSpecVer
519 CabalSpecV2_0
520 (not . null $ mixins bi)
521 (PackageDistInexcusable CVMixins)
523 checkBuildInfoExtensions bi
524 where
525 checkCVSources :: Monad m => [FilePath] -> CheckM m ()
526 checkCVSources cvs =
527 checkSpecVer
528 CabalSpecV3_0
529 (not . null $ cvs)
530 (PackageDistInexcusable CVSources)
532 checkDefaultLanguage :: Monad m => CheckM m ()
533 checkDefaultLanguage = do
534 -- < 1.10 has no `default-language` field.
535 when
536 (sv >= CabalSpecV1_10 && isNothing (defaultLanguage bi))
537 -- < 3.4 mandatory, after just a suggestion.
538 ( if sv < CabalSpecV3_4
539 then tellP (PackageBuildWarning CVDefaultLanguageComponent)
540 else tellP (PackageDistInexcusable CVDefaultLanguageComponentSoft)
543 -- Tests for extensions usage which can break Cabal < 1.4.
544 checkBuildInfoExtensions :: Monad m => BuildInfo -> CheckM m ()
545 checkBuildInfoExtensions bi = do
546 let exts = allExtensions bi
547 extCabal1_2 = nub $ filter (`elem` compatExtensionsExtra) exts
548 extCabal1_4 = nub $ filter (`notElem` compatExtensions) exts
549 -- As of Cabal-1.4 we can add new extensions without worrying
550 -- about breaking old versions of cabal.
551 checkSpecVer
552 CabalSpecV1_2
553 (not . null $ extCabal1_2)
554 ( PackageDistInexcusable $
555 CVExtensions CabalSpecV1_2 extCabal1_2
557 checkSpecVer
558 CabalSpecV1_4
559 (not . null $ extCabal1_4)
560 ( PackageDistInexcusable $
561 CVExtensions CabalSpecV1_4 extCabal1_4
563 where
564 -- The known extensions in Cabal-1.2.3
565 compatExtensions :: [Extension]
566 compatExtensions =
568 EnableExtension
569 [ OverlappingInstances
570 , UndecidableInstances
571 , IncoherentInstances
572 , RecursiveDo
573 , ParallelListComp
574 , MultiParamTypeClasses
575 , FunctionalDependencies
576 , Rank2Types
577 , RankNTypes
578 , PolymorphicComponents
579 , ExistentialQuantification
580 , ScopedTypeVariables
581 , ImplicitParams
582 , FlexibleContexts
583 , FlexibleInstances
584 , EmptyDataDecls
585 , CPP
586 , BangPatterns
587 , TypeSynonymInstances
588 , TemplateHaskell
589 , ForeignFunctionInterface
590 , Arrows
591 , Generics
592 , NamedFieldPuns
593 , PatternGuards
594 , GeneralizedNewtypeDeriving
595 , ExtensibleRecords
596 , RestrictedTypeSynonyms
597 , HereDocuments
599 ++ map
600 DisableExtension
601 [MonomorphismRestriction, ImplicitPrelude]
602 ++ compatExtensionsExtra
604 -- The extra known extensions in Cabal-1.2.3 vs Cabal-1.1.6
605 -- (Cabal-1.1.6 came with ghc-6.6. Cabal-1.2 came with ghc-6.8)
606 compatExtensionsExtra :: [Extension]
607 compatExtensionsExtra =
609 EnableExtension
610 [ KindSignatures
611 , MagicHash
612 , TypeFamilies
613 , StandaloneDeriving
614 , UnicodeSyntax
615 , PatternSignatures
616 , UnliftedFFITypes
617 , LiberalTypeSynonyms
618 , TypeOperators
619 , RecordWildCards
620 , RecordPuns
621 , DisambiguateRecordFields
622 , OverloadedStrings
623 , GADTs
624 , RelaxedPolyRec
625 , ExtendedDefaultRules
626 , UnboxedTuples
627 , DeriveDataTypeable
628 , ConstrainedClassMethods
630 ++ map
631 DisableExtension
632 [MonoPatBinds]
634 -- Autogenerated modules (Paths_, PackageInfo_) checks. We could pass this
635 -- function something more specific than the whole BuildInfo, but it would be
636 -- a tuple of [ModuleName] lists, error prone.
637 checkAutogenModules
638 :: Monad m
639 => [ModuleName] -- Additional modules not present
640 -- in BuildInfo (e.g. exposed library
641 -- modules).
642 -> BuildInfo
643 -> CheckM m ()
644 checkAutogenModules ams bi = do
645 pkgId <- asksCM (pnPackageId . ccNames)
647 -- It is an unfortunate reality that autogenPathsModuleName
648 -- and autogenPackageInfoModuleName work on PackageDescription
649 -- while not needing it all, but just the `package` bit.
650 minimalPD = emptyPackageDescription{package = pkgId}
651 autoPathsName = autogenPathsModuleName minimalPD
652 autoInfoModuleName = autogenPackageInfoModuleName minimalPD
654 -- Autogenerated module + some default extension build failure.
655 autogenCheck autoPathsName CVAutogenPaths
656 rebindableClashCheck autoPathsName RebindableClashPaths
658 -- Paths_* module + some default extension build failure.
659 autogenCheck autoInfoModuleName CVAutogenPackageInfo
660 rebindableClashCheck autoInfoModuleName RebindableClashPackageInfo
662 -- PackageInfo_* module + cabal-version < 3.12
663 -- See Mikolaj’s comments on #9481 on why this has to be
664 -- PackageBuildImpossible and not merely PackageDistInexcusable.
665 checkSpecVer
666 CabalSpecV3_12
667 (elem autoInfoModuleName allModsForAuto)
668 (PackageBuildImpossible CVAutogenPackageInfoGuard)
669 where
670 allModsForAuto :: [ModuleName]
671 allModsForAuto = ams ++ otherModules bi
673 autogenCheck
674 :: Monad m
675 => ModuleName
676 -> CheckExplanation
677 -> CheckM m ()
678 autogenCheck name warning = do
679 sv <- asksCM ccSpecVersion
680 checkP
681 ( sv >= CabalSpecV2_0
682 && elem name allModsForAuto
683 && notElem name (autogenModules bi)
685 (PackageDistInexcusable warning)
687 rebindableClashCheck
688 :: Monad m
689 => ModuleName
690 -> CheckExplanation
691 -> CheckM m ()
692 rebindableClashCheck name warning = do
693 checkSpecVer
694 CabalSpecV2_2
695 ( ( name `elem` otherModules bi
696 || name `elem` autogenModules bi
698 && checkExts
700 (PackageBuildImpossible warning)
702 -- Do we have some peculiar extensions active which would interfere
703 -- (cabal-version <2.2) with Paths_modules?
704 checkExts :: Bool
705 checkExts =
706 let exts = defaultExtensions bi
707 in rebind `elem` exts
708 && (strings `elem` exts || lists `elem` exts)
709 where
710 rebind = EnableExtension RebindableSyntax
711 strings = EnableExtension OverloadedStrings
712 lists = EnableExtension OverloadedLists
714 checkLocalPathExist
715 :: Monad m
716 => String -- .cabal field where we found the error.
717 -> FilePath
718 -> CheckM m ()
719 checkLocalPathExist title dir =
720 checkPkg
721 ( \ops -> do
722 dn <- not <$> doesDirectoryExist ops dir
723 let rp = not (isAbsoluteOnAnyPlatform dir)
724 return (rp && dn)
726 (PackageBuildWarning $ UnknownDirectory title dir)
728 -- PVP --
730 -- Sometimes we read (or end up with) “straddle” deps declarations
731 -- like this:
733 -- build-depends: base > 3, base < 4
735 -- `mergeDependencies` reduces that to base > 3 && < 4, _while_ maintaining
736 -- dependencies order in the list (better UX).
737 mergeDependencies :: [Dependency] -> [Dependency]
738 mergeDependencies [] = []
739 mergeDependencies l@(d : _) =
740 let (sames, diffs) = partition ((== depName d) . depName) l
741 merged =
742 Dependency
743 (depPkgName d)
744 ( foldl intersectVersionRanges anyVersion $
745 map depVerRange sames
747 (depLibraries d)
748 in merged : mergeDependencies diffs
749 where
750 depName :: Dependency -> String
751 depName wd = unPackageName . depPkgName $ wd
753 -- Is this an internal target? We do not perform PVP checks on those,
754 -- see https://github.com/haskell/cabal/pull/8361#issuecomment-1577547091
755 isInternalTarget :: CEType -> Bool
756 isInternalTarget (CETLibrary{}) = False
757 isInternalTarget (CETForeignLibrary{}) = False
758 isInternalTarget (CETExecutable{}) = False
759 isInternalTarget (CETTest{}) = True
760 isInternalTarget (CETBenchmark{}) = True
761 isInternalTarget (CETSetup{}) = False
763 -- ------------------------------------------------------------
764 -- Options
765 -- ------------------------------------------------------------
767 -- Target type for option checking.
768 data BITarget = BITLib | BITTestBench | BITOther
769 deriving (Eq, Show)
771 cet2bit :: CEType -> BITarget
772 cet2bit (CETLibrary{}) = BITLib
773 cet2bit (CETForeignLibrary{}) = BITLib
774 cet2bit (CETExecutable{}) = BITOther
775 cet2bit (CETTest{}) = BITTestBench
776 cet2bit (CETBenchmark{}) = BITTestBench
777 cet2bit CETSetup = BITOther
779 -- General check on all options (ghc, C, C++, …) for common inaccuracies.
780 checkBuildInfoOptions :: Monad m => BITarget -> BuildInfo -> CheckM m ()
781 checkBuildInfoOptions t bi = do
782 checkGHCOptions "ghc-options" t (hcOptions GHC bi)
783 checkGHCOptions "ghc-prof-options" t (hcProfOptions GHC bi)
784 checkGHCOptions "ghc-shared-options" t (hcSharedOptions GHC bi)
785 let ldOpts = ldOptions bi
786 checkCLikeOptions LangC "cc-options" (ccOptions bi) ldOpts
787 checkCLikeOptions LangCPlusPlus "cxx-options" (cxxOptions bi) ldOpts
788 checkCPPOptions (cppOptions bi)
790 -- | Checks GHC options for commonly misused or non-portable flags.
791 checkGHCOptions
792 :: Monad m
793 => CabalField -- .cabal field name where we found the error.
794 -> BITarget -- Target type.
795 -> [String] -- Options (alas in String form).
796 -> CheckM m ()
797 checkGHCOptions title t opts = do
798 checkGeneral
799 case t of
800 BITLib -> sequence_ [checkLib, checkNonTestBench]
801 BITTestBench -> checkTestBench
802 BITOther -> checkNonTestBench
803 where
804 checkFlags :: Monad m => [String] -> PackageCheck -> CheckM m ()
805 checkFlags fs ck = checkP (any (`elem` fs) opts) ck
807 checkFlagsP
808 :: Monad m
809 => (String -> Bool)
810 -> (String -> PackageCheck)
811 -> CheckM m ()
812 checkFlagsP p ckc =
813 case filter p opts of
814 [] -> return ()
815 (_ : _) -> tellP (ckc title)
817 checkGeneral = do
818 checkFlags
819 ["-fasm"]
820 (PackageDistInexcusable $ OptFasm title)
821 checkFlags
822 ["-fhpc"]
823 (PackageDistInexcusable $ OptHpc title)
824 checkFlags
825 ["-prof"]
826 (PackageBuildWarning $ OptProf title)
827 -- Does not apply to scripts.
828 -- Why do we need this? See #8963.
829 pid <- asksCM (pnPackageId . ccNames)
830 unless (pid == fakePackageId) $
831 checkFlags
832 ["-o"]
833 (PackageBuildWarning $ OptO title)
834 checkFlags
835 ["-hide-package"]
836 (PackageBuildWarning $ OptHide title)
837 checkFlags
838 ["--make"]
839 (PackageBuildWarning $ OptMake title)
840 checkFlags
841 ["-O", "-O1"]
842 (PackageDistInexcusable $ OptOOne title)
843 checkFlags
844 ["-O2"]
845 (PackageDistSuspiciousWarn $ OptOTwo title)
846 checkFlags
847 ["-split-sections"]
848 (PackageBuildWarning $ OptSplitSections title)
849 checkFlags
850 ["-split-objs"]
851 (PackageBuildWarning $ OptSplitObjs title)
852 checkFlags
853 ["-optl-Wl,-s", "-optl-s"]
854 (PackageDistInexcusable $ OptWls title)
855 checkFlags
856 ["-fglasgow-exts"]
857 (PackageDistSuspicious $ OptExts title)
858 let ghcNoRts = rmRtsOpts opts
859 checkAlternatives
860 title
861 "extensions"
862 [ (flag, prettyShow extension)
863 | flag <- ghcNoRts
864 , Just extension <- [ghcExtension flag]
866 checkAlternatives
867 title
868 "extensions"
869 [ (flag, extension)
870 | flag@('-' : 'X' : extension) <- ghcNoRts
872 checkAlternatives
873 title
874 "cpp-options"
875 ( [(flag, flag) | flag@('-' : 'D' : _) <- ghcNoRts]
876 ++ [(flag, flag) | flag@('-' : 'U' : _) <- ghcNoRts]
878 checkAlternatives
879 title
880 "include-dirs"
881 [(flag, dir) | flag@('-' : 'I' : dir) <- ghcNoRts]
882 checkAlternatives
883 title
884 "extra-libraries"
885 [(flag, lib) | flag@('-' : 'l' : lib) <- ghcNoRts]
886 checkAlternatives
887 title
888 "extra-libraries-static"
889 [(flag, lib) | flag@('-' : 'l' : lib) <- ghcNoRts]
890 checkAlternatives
891 title
892 "extra-lib-dirs"
893 [(flag, dir) | flag@('-' : 'L' : dir) <- ghcNoRts]
894 checkAlternatives
895 title
896 "extra-lib-dirs-static"
897 [(flag, dir) | flag@('-' : 'L' : dir) <- ghcNoRts]
898 checkAlternatives
899 title
900 "frameworks"
901 [ (flag, fmwk)
902 | (flag@"-framework", fmwk) <-
903 zip ghcNoRts (safeTail ghcNoRts)
905 checkAlternatives
906 title
907 "extra-framework-dirs"
908 [ (flag, dir)
909 | (flag@"-framework-path", dir) <-
910 zip ghcNoRts (safeTail ghcNoRts)
912 -- Old `checkDevelopmentOnlyFlagsOptions` section
913 checkFlags
914 ["-Werror"]
915 (PackageDistInexcusable $ WErrorUnneeded title)
916 checkFlags
917 ["-fdefer-type-errors"]
918 (PackageDistInexcusable $ FDeferTypeErrorsUnneeded title)
919 checkFlags
920 [ "-fprof-auto"
921 , "-fprof-auto-top"
922 , "-fprof-auto-calls"
923 , "-fprof-cafs"
924 , "-fno-prof-count-entries"
925 , "-auto-all"
926 , "-auto"
927 , "-caf-all"
929 (PackageDistSuspicious $ ProfilingUnneeded title)
930 checkFlagsP
931 ( \opt ->
932 "-d" `isPrefixOf` opt
933 && opt /= "-dynamic"
935 (PackageDistInexcusable . DynamicUnneeded)
936 checkFlagsP
937 ( \opt -> case opt of
938 "-j" -> True
939 ('-' : 'j' : d : _) -> isDigit d
940 _ -> False
942 (PackageDistInexcusable . JUnneeded)
944 checkLib = do
945 checkP
946 ("-rtsopts" `elem` opts)
947 (PackageBuildWarning $ OptRts title)
948 checkP
949 (any (\opt -> "-with-rtsopts" `isPrefixOf` opt) opts)
950 (PackageBuildWarning $ OptWithRts title)
952 checkTestBench = do
953 checkFlags
954 ["-O0", "-Onot"]
955 (PackageDistSuspiciousWarn $ OptONot title)
957 checkNonTestBench = do
958 checkFlags
959 ["-O0", "-Onot"]
960 (PackageDistSuspicious $ OptONot title)
962 ghcExtension ('-' : 'f' : name) = case name of
963 "allow-overlapping-instances" -> enable OverlappingInstances
964 "no-allow-overlapping-instances" -> disable OverlappingInstances
965 "th" -> enable TemplateHaskell
966 "no-th" -> disable TemplateHaskell
967 "ffi" -> enable ForeignFunctionInterface
968 "no-ffi" -> disable ForeignFunctionInterface
969 "fi" -> enable ForeignFunctionInterface
970 "no-fi" -> disable ForeignFunctionInterface
971 "monomorphism-restriction" -> enable MonomorphismRestriction
972 "no-monomorphism-restriction" -> disable MonomorphismRestriction
973 "mono-pat-binds" -> enable MonoPatBinds
974 "no-mono-pat-binds" -> disable MonoPatBinds
975 "allow-undecidable-instances" -> enable UndecidableInstances
976 "no-allow-undecidable-instances" -> disable UndecidableInstances
977 "allow-incoherent-instances" -> enable IncoherentInstances
978 "no-allow-incoherent-instances" -> disable IncoherentInstances
979 "arrows" -> enable Arrows
980 "no-arrows" -> disable Arrows
981 "generics" -> enable Generics
982 "no-generics" -> disable Generics
983 "implicit-prelude" -> enable ImplicitPrelude
984 "no-implicit-prelude" -> disable ImplicitPrelude
985 "implicit-params" -> enable ImplicitParams
986 "no-implicit-params" -> disable ImplicitParams
987 "bang-patterns" -> enable BangPatterns
988 "no-bang-patterns" -> disable BangPatterns
989 "scoped-type-variables" -> enable ScopedTypeVariables
990 "no-scoped-type-variables" -> disable ScopedTypeVariables
991 "extended-default-rules" -> enable ExtendedDefaultRules
992 "no-extended-default-rules" -> disable ExtendedDefaultRules
993 _ -> Nothing
994 ghcExtension "-cpp" = enable CPP
995 ghcExtension _ = Nothing
997 enable e = Just (EnableExtension e)
998 disable e = Just (DisableExtension e)
1000 rmRtsOpts :: [String] -> [String]
1001 rmRtsOpts ("-with-rtsopts" : _ : xs) = rmRtsOpts xs
1002 rmRtsOpts (x : xs) = x : rmRtsOpts xs
1003 rmRtsOpts [] = []
1005 checkCLikeOptions
1006 :: Monad m
1007 => WarnLang -- Language we are warning about (C or C++).
1008 -> CabalField -- Field where we found the error.
1009 -> [String] -- Options in string form.
1010 -> [String] -- Link options in String form.
1011 -> CheckM m ()
1012 checkCLikeOptions label prefix opts ldOpts = do
1013 checkAlternatives
1014 prefix
1015 "include-dirs"
1016 [(flag, dir) | flag@('-' : 'I' : dir) <- opts]
1017 checkAlternatives
1018 prefix
1019 "extra-libraries"
1020 [(flag, lib) | flag@('-' : 'l' : lib) <- opts]
1021 checkAlternatives
1022 prefix
1023 "extra-lib-dirs"
1024 [(flag, dir) | flag@('-' : 'L' : dir) <- opts]
1026 checkAlternatives
1027 "ld-options"
1028 "extra-libraries"
1029 [(flag, lib) | flag@('-' : 'l' : lib) <- ldOpts]
1030 checkAlternatives
1031 "ld-options"
1032 "extra-lib-dirs"
1033 [(flag, dir) | flag@('-' : 'L' : dir) <- ldOpts]
1035 checkP
1036 (any (`elem` ["-O", "-Os", "-O0", "-O1", "-O2", "-O3"]) opts)
1037 (PackageDistSuspicious $ COptONumber prefix label)
1039 checkAlternatives
1040 :: Monad m
1041 => CabalField -- Wrong field.
1042 -> CabalField -- Appropriate field.
1043 -> [(String, String)] -- List of good and bad flags.
1044 -> CheckM m ()
1045 checkAlternatives badField goodField flags = do
1046 let (badFlags, _) = unzip flags
1047 checkP
1048 (not $ null badFlags)
1049 (PackageBuildWarning $ OptAlternatives badField goodField flags)
1051 checkCPPOptions
1052 :: Monad m
1053 => [String] -- Options in String form.
1054 -> CheckM m ()
1055 checkCPPOptions opts = do
1056 checkAlternatives
1057 "cpp-options"
1058 "include-dirs"
1059 [(flag, dir) | flag@('-' : 'I' : dir) <- opts]
1060 mapM_
1061 ( \opt ->
1062 checkP
1063 (not $ any (`isPrefixOf` opt) ["-D", "-U", "-I"])
1064 (PackageBuildWarning (COptCPP opt))
1066 opts