Make `check` recognise `main-is` in conditional branches (#9768)
[cabal.git] / Cabal / src / Distribution / PackageDescription / Check / Target.hs
blobe6cfba74928f28945f53d87f28db22f682c8a750
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 checkP
487 ( sv >= CabalSpecV1_10
488 && sv < CabalSpecV3_4
489 && isNothing (defaultLanguage bi)
491 (PackageBuildWarning CVDefaultLanguageComponent)
492 -- Check use of 'extra-framework-dirs' field.
493 checkSpecVer
494 CabalSpecV1_24
495 (not . null $ extraFrameworkDirs bi)
496 (PackageDistSuspiciousWarn CVExtraFrameworkDirs)
497 -- Check use of default-extensions field don't need to do the
498 -- equivalent check for other-extensions.
499 checkSpecVer
500 CabalSpecV1_10
501 (not . null $ defaultExtensions bi)
502 (PackageBuildWarning CVDefaultExtensions)
503 -- Check use of extensions field
504 checkP
505 (sv >= CabalSpecV1_10 && (not . null $ oldExtensions bi))
506 (PackageBuildWarning CVExtensionsDeprecated)
508 -- asm-sources, cmm-sources and friends only w/ spec ≥ 1.10
509 checkCVSources (asmSources bi)
510 checkCVSources (cmmSources bi)
511 checkCVSources (extraBundledLibs bi)
512 checkCVSources (extraLibFlavours bi)
514 -- extra-dynamic-library-flavours requires ≥ 3.0
515 checkSpecVer
516 CabalSpecV3_0
517 (not . null $ extraDynLibFlavours bi)
518 (PackageDistInexcusable $ CVExtraDynamic [extraDynLibFlavours bi])
519 -- virtual-modules requires ≥ 2.2
520 checkSpecVer CabalSpecV2_2 (not . null $ virtualModules bi) $
521 (PackageDistInexcusable CVVirtualModules)
522 -- Check use of thinning and renaming.
523 checkSpecVer
524 CabalSpecV2_0
525 (not . null $ mixins bi)
526 (PackageDistInexcusable CVMixins)
528 checkBuildInfoExtensions bi
529 where
530 checkCVSources :: Monad m => [FilePath] -> CheckM m ()
531 checkCVSources cvs =
532 checkSpecVer
533 CabalSpecV3_0
534 (not . null $ cvs)
535 (PackageDistInexcusable CVSources)
537 -- Tests for extensions usage which can break Cabal < 1.4.
538 checkBuildInfoExtensions :: Monad m => BuildInfo -> CheckM m ()
539 checkBuildInfoExtensions bi = do
540 let exts = allExtensions bi
541 extCabal1_2 = nub $ filter (`elem` compatExtensionsExtra) exts
542 extCabal1_4 = nub $ filter (`notElem` compatExtensions) exts
543 -- As of Cabal-1.4 we can add new extensions without worrying
544 -- about breaking old versions of cabal.
545 checkSpecVer
546 CabalSpecV1_2
547 (not . null $ extCabal1_2)
548 ( PackageDistInexcusable $
549 CVExtensions CabalSpecV1_2 extCabal1_2
551 checkSpecVer
552 CabalSpecV1_4
553 (not . null $ extCabal1_4)
554 ( PackageDistInexcusable $
555 CVExtensions CabalSpecV1_4 extCabal1_4
557 where
558 -- The known extensions in Cabal-1.2.3
559 compatExtensions :: [Extension]
560 compatExtensions =
562 EnableExtension
563 [ OverlappingInstances
564 , UndecidableInstances
565 , IncoherentInstances
566 , RecursiveDo
567 , ParallelListComp
568 , MultiParamTypeClasses
569 , FunctionalDependencies
570 , Rank2Types
571 , RankNTypes
572 , PolymorphicComponents
573 , ExistentialQuantification
574 , ScopedTypeVariables
575 , ImplicitParams
576 , FlexibleContexts
577 , FlexibleInstances
578 , EmptyDataDecls
579 , CPP
580 , BangPatterns
581 , TypeSynonymInstances
582 , TemplateHaskell
583 , ForeignFunctionInterface
584 , Arrows
585 , Generics
586 , NamedFieldPuns
587 , PatternGuards
588 , GeneralizedNewtypeDeriving
589 , ExtensibleRecords
590 , RestrictedTypeSynonyms
591 , HereDocuments
593 ++ map
594 DisableExtension
595 [MonomorphismRestriction, ImplicitPrelude]
596 ++ compatExtensionsExtra
598 -- The extra known extensions in Cabal-1.2.3 vs Cabal-1.1.6
599 -- (Cabal-1.1.6 came with ghc-6.6. Cabal-1.2 came with ghc-6.8)
600 compatExtensionsExtra :: [Extension]
601 compatExtensionsExtra =
603 EnableExtension
604 [ KindSignatures
605 , MagicHash
606 , TypeFamilies
607 , StandaloneDeriving
608 , UnicodeSyntax
609 , PatternSignatures
610 , UnliftedFFITypes
611 , LiberalTypeSynonyms
612 , TypeOperators
613 , RecordWildCards
614 , RecordPuns
615 , DisambiguateRecordFields
616 , OverloadedStrings
617 , GADTs
618 , RelaxedPolyRec
619 , ExtendedDefaultRules
620 , UnboxedTuples
621 , DeriveDataTypeable
622 , ConstrainedClassMethods
624 ++ map
625 DisableExtension
626 [MonoPatBinds]
628 -- Autogenerated modules (Paths_, PackageInfo_) checks. We could pass this
629 -- function something more specific than the whole BuildInfo, but it would be
630 -- a tuple of [ModuleName] lists, error prone.
631 checkAutogenModules
632 :: Monad m
633 => [ModuleName] -- Additional modules not present
634 -- in BuildInfo (e.g. exposed library
635 -- modules).
636 -> BuildInfo
637 -> CheckM m ()
638 checkAutogenModules ams bi = do
639 pkgId <- asksCM (pnPackageId . ccNames)
641 -- It is an unfortunate reality that autogenPathsModuleName
642 -- and autogenPackageInfoModuleName work on PackageDescription
643 -- while not needing it all, but just the `package` bit.
644 minimalPD = emptyPackageDescription{package = pkgId}
645 autoPathsName = autogenPathsModuleName minimalPD
646 autoInfoModuleName = autogenPackageInfoModuleName minimalPD
648 -- Autogenerated module + some default extension build failure.
649 autogenCheck autoPathsName CVAutogenPaths
650 rebindableClashCheck autoPathsName RebindableClashPaths
652 -- Paths_* module + some default extension build failure.
653 autogenCheck autoInfoModuleName CVAutogenPackageInfo
654 rebindableClashCheck autoInfoModuleName RebindableClashPackageInfo
656 -- PackageInfo_* module + cabal-version < 3.12
657 -- See Mikolaj’s comments on #9481 on why this has to be
658 -- PackageBuildImpossible and not merely PackageDistInexcusable.
659 checkSpecVer
660 CabalSpecV3_12
661 (elem autoInfoModuleName allModsForAuto)
662 (PackageBuildImpossible CVAutogenPackageInfoGuard)
663 where
664 allModsForAuto :: [ModuleName]
665 allModsForAuto = ams ++ otherModules bi
667 autogenCheck
668 :: Monad m
669 => ModuleName
670 -> CheckExplanation
671 -> CheckM m ()
672 autogenCheck name warning = do
673 sv <- asksCM ccSpecVersion
674 checkP
675 ( sv >= CabalSpecV2_0
676 && elem name allModsForAuto
677 && notElem name (autogenModules bi)
679 (PackageDistInexcusable warning)
681 rebindableClashCheck
682 :: Monad m
683 => ModuleName
684 -> CheckExplanation
685 -> CheckM m ()
686 rebindableClashCheck name warning = do
687 checkSpecVer
688 CabalSpecV2_2
689 ( ( name `elem` otherModules bi
690 || name `elem` autogenModules bi
692 && checkExts
694 (PackageBuildImpossible warning)
696 -- Do we have some peculiar extensions active which would interfere
697 -- (cabal-version <2.2) with Paths_modules?
698 checkExts :: Bool
699 checkExts =
700 let exts = defaultExtensions bi
701 in rebind `elem` exts
702 && (strings `elem` exts || lists `elem` exts)
703 where
704 rebind = EnableExtension RebindableSyntax
705 strings = EnableExtension OverloadedStrings
706 lists = EnableExtension OverloadedLists
708 checkLocalPathExist
709 :: Monad m
710 => String -- .cabal field where we found the error.
711 -> FilePath
712 -> CheckM m ()
713 checkLocalPathExist title dir =
714 checkPkg
715 ( \ops -> do
716 dn <- not <$> doesDirectoryExist ops dir
717 let rp = not (isAbsoluteOnAnyPlatform dir)
718 return (rp && dn)
720 (PackageBuildWarning $ UnknownDirectory title dir)
722 -- PVP --
724 -- Sometimes we read (or end up with) “straddle” deps declarations
725 -- like this:
727 -- build-depends: base > 3, base < 4
729 -- `mergeDependencies` reduces that to base > 3 && < 4, _while_ maintaining
730 -- dependencies order in the list (better UX).
731 mergeDependencies :: [Dependency] -> [Dependency]
732 mergeDependencies [] = []
733 mergeDependencies l@(d : _) =
734 let (sames, diffs) = partition ((== depName d) . depName) l
735 merged =
736 Dependency
737 (depPkgName d)
738 ( foldl intersectVersionRanges anyVersion $
739 map depVerRange sames
741 (depLibraries d)
742 in merged : mergeDependencies diffs
743 where
744 depName :: Dependency -> String
745 depName wd = unPackageName . depPkgName $ wd
747 -- Is this an internal target? We do not perform PVP checks on those,
748 -- see https://github.com/haskell/cabal/pull/8361#issuecomment-1577547091
749 isInternalTarget :: CEType -> Bool
750 isInternalTarget (CETLibrary{}) = False
751 isInternalTarget (CETForeignLibrary{}) = False
752 isInternalTarget (CETExecutable{}) = False
753 isInternalTarget (CETTest{}) = True
754 isInternalTarget (CETBenchmark{}) = True
755 isInternalTarget (CETSetup{}) = False
757 -- ------------------------------------------------------------
758 -- Options
759 -- ------------------------------------------------------------
761 -- Target type for option checking.
762 data BITarget = BITLib | BITTestBench | BITOther
763 deriving (Eq, Show)
765 cet2bit :: CEType -> BITarget
766 cet2bit (CETLibrary{}) = BITLib
767 cet2bit (CETForeignLibrary{}) = BITLib
768 cet2bit (CETExecutable{}) = BITOther
769 cet2bit (CETTest{}) = BITTestBench
770 cet2bit (CETBenchmark{}) = BITTestBench
771 cet2bit CETSetup = BITOther
773 -- General check on all options (ghc, C, C++, …) for common inaccuracies.
774 checkBuildInfoOptions :: Monad m => BITarget -> BuildInfo -> CheckM m ()
775 checkBuildInfoOptions t bi = do
776 checkGHCOptions "ghc-options" t (hcOptions GHC bi)
777 checkGHCOptions "ghc-prof-options" t (hcProfOptions GHC bi)
778 checkGHCOptions "ghc-shared-options" t (hcSharedOptions GHC bi)
779 let ldOpts = ldOptions bi
780 checkCLikeOptions LangC "cc-options" (ccOptions bi) ldOpts
781 checkCLikeOptions LangCPlusPlus "cxx-options" (cxxOptions bi) ldOpts
782 checkCPPOptions (cppOptions bi)
784 -- | Checks GHC options for commonly misused or non-portable flags.
785 checkGHCOptions
786 :: Monad m
787 => CabalField -- .cabal field name where we found the error.
788 -> BITarget -- Target type.
789 -> [String] -- Options (alas in String form).
790 -> CheckM m ()
791 checkGHCOptions title t opts = do
792 checkGeneral
793 case t of
794 BITLib -> sequence_ [checkLib, checkNonTestBench]
795 BITTestBench -> checkTestBench
796 BITOther -> checkNonTestBench
797 where
798 checkFlags :: Monad m => [String] -> PackageCheck -> CheckM m ()
799 checkFlags fs ck = checkP (any (`elem` fs) opts) ck
801 checkFlagsP
802 :: Monad m
803 => (String -> Bool)
804 -> (String -> PackageCheck)
805 -> CheckM m ()
806 checkFlagsP p ckc =
807 case filter p opts of
808 [] -> return ()
809 (_ : _) -> tellP (ckc title)
811 checkGeneral = do
812 checkFlags
813 ["-fasm"]
814 (PackageDistInexcusable $ OptFasm title)
815 checkFlags
816 ["-fhpc"]
817 (PackageDistInexcusable $ OptHpc title)
818 checkFlags
819 ["-prof"]
820 (PackageBuildWarning $ OptProf title)
821 -- Does not apply to scripts.
822 -- Why do we need this? See #8963.
823 pid <- asksCM (pnPackageId . ccNames)
824 unless (pid == fakePackageId) $
825 checkFlags
826 ["-o"]
827 (PackageBuildWarning $ OptO title)
828 checkFlags
829 ["-hide-package"]
830 (PackageBuildWarning $ OptHide title)
831 checkFlags
832 ["--make"]
833 (PackageBuildWarning $ OptMake title)
834 checkFlags
835 ["-O", "-O1"]
836 (PackageDistInexcusable $ OptOOne title)
837 checkFlags
838 ["-O2"]
839 (PackageDistSuspiciousWarn $ OptOTwo title)
840 checkFlags
841 ["-split-sections"]
842 (PackageBuildWarning $ OptSplitSections title)
843 checkFlags
844 ["-split-objs"]
845 (PackageBuildWarning $ OptSplitObjs title)
846 checkFlags
847 ["-optl-Wl,-s", "-optl-s"]
848 (PackageDistInexcusable $ OptWls title)
849 checkFlags
850 ["-fglasgow-exts"]
851 (PackageDistSuspicious $ OptExts title)
852 let ghcNoRts = rmRtsOpts opts
853 checkAlternatives
854 title
855 "extensions"
856 [ (flag, prettyShow extension)
857 | flag <- ghcNoRts
858 , Just extension <- [ghcExtension flag]
860 checkAlternatives
861 title
862 "extensions"
863 [ (flag, extension)
864 | flag@('-' : 'X' : extension) <- ghcNoRts
866 checkAlternatives
867 title
868 "cpp-options"
869 ( [(flag, flag) | flag@('-' : 'D' : _) <- ghcNoRts]
870 ++ [(flag, flag) | flag@('-' : 'U' : _) <- ghcNoRts]
872 checkAlternatives
873 title
874 "include-dirs"
875 [(flag, dir) | flag@('-' : 'I' : dir) <- ghcNoRts]
876 checkAlternatives
877 title
878 "extra-libraries"
879 [(flag, lib) | flag@('-' : 'l' : lib) <- ghcNoRts]
880 checkAlternatives
881 title
882 "extra-libraries-static"
883 [(flag, lib) | flag@('-' : 'l' : lib) <- ghcNoRts]
884 checkAlternatives
885 title
886 "extra-lib-dirs"
887 [(flag, dir) | flag@('-' : 'L' : dir) <- ghcNoRts]
888 checkAlternatives
889 title
890 "extra-lib-dirs-static"
891 [(flag, dir) | flag@('-' : 'L' : dir) <- ghcNoRts]
892 checkAlternatives
893 title
894 "frameworks"
895 [ (flag, fmwk)
896 | (flag@"-framework", fmwk) <-
897 zip ghcNoRts (safeTail ghcNoRts)
899 checkAlternatives
900 title
901 "extra-framework-dirs"
902 [ (flag, dir)
903 | (flag@"-framework-path", dir) <-
904 zip ghcNoRts (safeTail ghcNoRts)
906 -- Old `checkDevelopmentOnlyFlagsOptions` section
907 checkFlags
908 ["-Werror"]
909 (PackageDistInexcusable $ WErrorUnneeded title)
910 checkFlags
911 ["-fdefer-type-errors"]
912 (PackageDistInexcusable $ FDeferTypeErrorsUnneeded title)
913 checkFlags
914 [ "-fprof-auto"
915 , "-fprof-auto-top"
916 , "-fprof-auto-calls"
917 , "-fprof-cafs"
918 , "-fno-prof-count-entries"
919 , "-auto-all"
920 , "-auto"
921 , "-caf-all"
923 (PackageDistSuspicious $ ProfilingUnneeded title)
924 checkFlagsP
925 ( \opt ->
926 "-d" `isPrefixOf` opt
927 && opt /= "-dynamic"
929 (PackageDistInexcusable . DynamicUnneeded)
930 checkFlagsP
931 ( \opt -> case opt of
932 "-j" -> True
933 ('-' : 'j' : d : _) -> isDigit d
934 _ -> False
936 (PackageDistInexcusable . JUnneeded)
938 checkLib = do
939 checkP
940 ("-rtsopts" `elem` opts)
941 (PackageBuildWarning $ OptRts title)
942 checkP
943 (any (\opt -> "-with-rtsopts" `isPrefixOf` opt) opts)
944 (PackageBuildWarning $ OptWithRts title)
946 checkTestBench = do
947 checkFlags
948 ["-O0", "-Onot"]
949 (PackageDistSuspiciousWarn $ OptONot title)
951 checkNonTestBench = do
952 checkFlags
953 ["-O0", "-Onot"]
954 (PackageDistSuspicious $ OptONot title)
956 ghcExtension ('-' : 'f' : name) = case name of
957 "allow-overlapping-instances" -> enable OverlappingInstances
958 "no-allow-overlapping-instances" -> disable OverlappingInstances
959 "th" -> enable TemplateHaskell
960 "no-th" -> disable TemplateHaskell
961 "ffi" -> enable ForeignFunctionInterface
962 "no-ffi" -> disable ForeignFunctionInterface
963 "fi" -> enable ForeignFunctionInterface
964 "no-fi" -> disable ForeignFunctionInterface
965 "monomorphism-restriction" -> enable MonomorphismRestriction
966 "no-monomorphism-restriction" -> disable MonomorphismRestriction
967 "mono-pat-binds" -> enable MonoPatBinds
968 "no-mono-pat-binds" -> disable MonoPatBinds
969 "allow-undecidable-instances" -> enable UndecidableInstances
970 "no-allow-undecidable-instances" -> disable UndecidableInstances
971 "allow-incoherent-instances" -> enable IncoherentInstances
972 "no-allow-incoherent-instances" -> disable IncoherentInstances
973 "arrows" -> enable Arrows
974 "no-arrows" -> disable Arrows
975 "generics" -> enable Generics
976 "no-generics" -> disable Generics
977 "implicit-prelude" -> enable ImplicitPrelude
978 "no-implicit-prelude" -> disable ImplicitPrelude
979 "implicit-params" -> enable ImplicitParams
980 "no-implicit-params" -> disable ImplicitParams
981 "bang-patterns" -> enable BangPatterns
982 "no-bang-patterns" -> disable BangPatterns
983 "scoped-type-variables" -> enable ScopedTypeVariables
984 "no-scoped-type-variables" -> disable ScopedTypeVariables
985 "extended-default-rules" -> enable ExtendedDefaultRules
986 "no-extended-default-rules" -> disable ExtendedDefaultRules
987 _ -> Nothing
988 ghcExtension "-cpp" = enable CPP
989 ghcExtension _ = Nothing
991 enable e = Just (EnableExtension e)
992 disable e = Just (DisableExtension e)
994 rmRtsOpts :: [String] -> [String]
995 rmRtsOpts ("-with-rtsopts" : _ : xs) = rmRtsOpts xs
996 rmRtsOpts (x : xs) = x : rmRtsOpts xs
997 rmRtsOpts [] = []
999 checkCLikeOptions
1000 :: Monad m
1001 => WarnLang -- Language we are warning about (C or C++).
1002 -> CabalField -- Field where we found the error.
1003 -> [String] -- Options in string form.
1004 -> [String] -- Link options in String form.
1005 -> CheckM m ()
1006 checkCLikeOptions label prefix opts ldOpts = do
1007 checkAlternatives
1008 prefix
1009 "include-dirs"
1010 [(flag, dir) | flag@('-' : 'I' : dir) <- opts]
1011 checkAlternatives
1012 prefix
1013 "extra-libraries"
1014 [(flag, lib) | flag@('-' : 'l' : lib) <- opts]
1015 checkAlternatives
1016 prefix
1017 "extra-lib-dirs"
1018 [(flag, dir) | flag@('-' : 'L' : dir) <- opts]
1020 checkAlternatives
1021 "ld-options"
1022 "extra-libraries"
1023 [(flag, lib) | flag@('-' : 'l' : lib) <- ldOpts]
1024 checkAlternatives
1025 "ld-options"
1026 "extra-lib-dirs"
1027 [(flag, dir) | flag@('-' : 'L' : dir) <- ldOpts]
1029 checkP
1030 (any (`elem` ["-O", "-Os", "-O0", "-O1", "-O2", "-O3"]) opts)
1031 (PackageDistSuspicious $ COptONumber prefix label)
1033 checkAlternatives
1034 :: Monad m
1035 => CabalField -- Wrong field.
1036 -> CabalField -- Appropriate field.
1037 -> [(String, String)] -- List of good and bad flags.
1038 -> CheckM m ()
1039 checkAlternatives badField goodField flags = do
1040 let (badFlags, _) = unzip flags
1041 checkP
1042 (not $ null badFlags)
1043 (PackageBuildWarning $ OptAlternatives badField goodField flags)
1045 checkCPPOptions
1046 :: Monad m
1047 => [String] -- Options in String form.
1048 -> CheckM m ()
1049 checkCPPOptions opts = do
1050 checkAlternatives
1051 "cpp-options"
1052 "include-dirs"
1053 [(flag, dir) | flag@('-' : 'I' : dir) <- opts]
1054 mapM_
1055 ( \opt ->
1056 checkP
1057 (not $ any (`isPrefixOf` opt) ["-D", "-U", "-I"])
1058 (PackageBuildWarning (COptCPP opt))
1060 opts