-
Notifications
You must be signed in to change notification settings - Fork 841
/
Package.hs
1098 lines (1045 loc) · 43.1 KB
/
Package.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE CPP #-}
-- | Dealing with Cabal.
module Stack.Package
(readPackage
,readPackageBS
,readPackageDir
,readPackageUnresolved
,readPackageUnresolvedBS
,resolvePackage
,getCabalFileName
,Package(..)
,GetPackageFiles(..)
,GetPackageOpts(..)
,PackageConfig(..)
,buildLogPath
,PackageException (..)
,resolvePackageDescription
,packageToolDependencies
,packageDependencies
,packageIdentifier
,autogenDir
,checkCabalFileName
,printCabalFileWarning)
where
import Control.Arrow ((&&&))
import Control.Exception hiding (try,catch)
import Control.Monad
import Control.Monad.Catch
import Control.Monad.IO.Class
import Control.Monad.Logger (MonadLogger,logWarn)
import Control.Monad.Reader
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as C8
import Data.Either
import Data.Function
import Data.List
import Data.List.Extra (nubOrd)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe
import Data.Maybe.Extra
import Data.Monoid
import Data.Set (Set)
import qualified Data.Set as S
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8, decodeUtf8With)
import Data.Text.Encoding.Error (lenientDecode)
import Distribution.Compiler
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as Cabal
import Distribution.Package hiding (Package,PackageName,packageName,packageVersion,PackageIdentifier)
import Distribution.PackageDescription hiding (FlagName)
import Distribution.PackageDescription.Parse
import Distribution.ParseUtils
import Distribution.Simple.Utils
import Distribution.System (OS (..), Arch, Platform (..))
import Distribution.Text (display, simpleParse)
import Path as FL
import Path.Extra
import Path.Find
import Path.IO
import Prelude
import Safe (headDef, tailSafe)
import Stack.Build.Installed
import Stack.Constants
import Stack.Types
import qualified Stack.Types.PackageIdentifier
import System.Directory (doesFileExist, getDirectoryContents)
import System.FilePath (splitExtensions, replaceExtension)
import qualified System.FilePath as FilePath
import System.IO.Error
packageIdentifier :: Package -> Stack.Types.PackageIdentifier.PackageIdentifier
packageIdentifier pkg =
Stack.Types.PackageIdentifier.PackageIdentifier
(packageName pkg)
(packageVersion pkg)
-- | Read the raw, unresolved package information.
readPackageUnresolved :: (MonadIO m, MonadThrow m)
=> Path Abs File
-> m ([PWarning],GenericPackageDescription)
readPackageUnresolved cabalfp =
liftIO (BS.readFile (FL.toFilePath cabalfp))
>>= readPackageUnresolvedBS (Just cabalfp)
-- | Read the raw, unresolved package information from a ByteString.
readPackageUnresolvedBS :: (MonadThrow m)
=> Maybe (Path Abs File)
-> BS.ByteString
-> m ([PWarning],GenericPackageDescription)
readPackageUnresolvedBS mcabalfp bs =
case parsePackageDescription chars of
ParseFailed per ->
throwM (PackageInvalidCabalFile mcabalfp per)
ParseOk warnings gpkg -> return (warnings,gpkg)
where
chars = T.unpack (dropBOM (decodeUtf8With lenientDecode bs))
-- https://github.com/haskell/hackage-server/issues/351
dropBOM t = fromMaybe t $ T.stripPrefix "\xFEFF" t
-- | Reads and exposes the package information
readPackage :: (MonadLogger m, MonadIO m, MonadThrow m, MonadCatch m)
=> PackageConfig
-> Path Abs File
-> m ([PWarning],Package)
readPackage packageConfig cabalfp =
do (warnings,gpkg) <- readPackageUnresolved cabalfp
return (warnings,resolvePackage packageConfig gpkg)
-- | Reads and exposes the package information, from a ByteString
readPackageBS :: (MonadThrow m)
=> PackageConfig
-> BS.ByteString
-> m ([PWarning],Package)
readPackageBS packageConfig bs =
do (warnings,gpkg) <- readPackageUnresolvedBS Nothing bs
return (warnings,resolvePackage packageConfig gpkg)
-- | Convenience wrapper around @readPackage@ that first finds the cabal file
-- in the given directory.
readPackageDir :: (MonadLogger m, MonadIO m, MonadThrow m, MonadCatch m)
=> PackageConfig
-> Path Abs Dir
-> m (Path Abs File, [PWarning], Package)
readPackageDir packageConfig dir = do
cabalfp <- getCabalFileName dir
(warnings,pkg) <- readPackage packageConfig cabalfp
checkCabalFileName (packageName pkg) cabalfp
return (cabalfp, warnings, pkg)
-- | Print cabal file warnings.
printCabalFileWarning
:: (MonadLogger m)
=> Path Abs File -> PWarning -> m ()
printCabalFileWarning cabalfp =
\case
(PWarning x) ->
$logWarn
("Cabal file warning in " <> T.pack (toFilePath cabalfp) <>
": " <>
T.pack x)
(UTFWarning line msg) ->
$logWarn
("Cabal file warning in " <> T.pack (toFilePath cabalfp) <> ":" <>
T.pack (show line) <>
": " <>
T.pack msg)
-- | Check if the given name in the @Package@ matches the name of the .cabal file
checkCabalFileName :: MonadThrow m => PackageName -> Path Abs File -> m ()
checkCabalFileName name cabalfp = do
-- Previously, we just use parsePackageNameFromFilePath. However, that can
-- lead to confusing error messages. See:
-- https://github.com/commercialhaskell/stack/issues/895
let expected = packageNameString name ++ ".cabal"
when (expected /= toFilePath (filename cabalfp))
$ throwM $ MismatchedCabalName cabalfp name
-- | Resolve a parsed cabal file into a 'Package'.
resolvePackage :: PackageConfig
-> GenericPackageDescription
-> Package
resolvePackage packageConfig gpkg =
Package
{ packageName = name
, packageVersion = fromCabalVersion (pkgVersion pkgId)
, packageDeps = deps
, packageFiles = pkgFiles
, packageTools = packageDescTools pkg
, packageFlags = packageConfigFlags packageConfig
, packageAllDeps = S.fromList (M.keys deps)
, packageHasLibrary = maybe False (buildable . libBuildInfo) (library pkg)
, packageTests = S.fromList
[T.pack (testName t) | t <- testSuites pkg
, buildable (testBuildInfo t)]
, packageBenchmarks = S.fromList
[T.pack (benchmarkName b) | b <- benchmarks pkg
, buildable (benchmarkBuildInfo b)]
, packageExes = S.fromList
[T.pack (exeName b) | b <- executables pkg
, buildable (buildInfo b)]
, packageOpts = GetPackageOpts $
\sourceMap installedMap omitPkgs cabalfp ->
do (componentsModules,componentFiles,_,_) <- getPackageFiles pkgFiles cabalfp
componentsOpts <-
generatePkgDescOpts sourceMap installedMap omitPkgs cabalfp pkg componentFiles
return (componentsModules,componentFiles,componentsOpts)
, packageHasExposedModules = maybe
False
(not . null . exposedModules)
(library pkg)
, packageSimpleType = buildType (packageDescription gpkg) == Just Simple
, packageDefinedFlags = S.fromList $
map (fromCabalFlagName . flagName) $ genPackageFlags gpkg
}
where
pkgFiles = GetPackageFiles $
\cabalfp ->
do distDir <- distDirFromDir (parent cabalfp)
(componentModules,componentFiles,dataFiles',warnings) <-
runReaderT
(packageDescModulesAndFiles pkg)
(cabalfp, buildDir distDir)
return (componentModules, componentFiles, S.insert cabalfp dataFiles', warnings)
pkgId = package (packageDescription gpkg)
name = fromCabalPackageName (pkgName pkgId)
pkg = resolvePackageDescription packageConfig gpkg
deps = M.filterWithKey (const . (/= name)) (packageDependencies pkg)
-- | Generate GHC options for the package's components, and a list of
-- options which apply generally to the package, not one specific
-- component.
generatePkgDescOpts
:: (HasEnvConfig env, HasPlatform env, MonadThrow m, MonadReader env m, MonadIO m)
=> SourceMap
-> InstalledMap
-> [PackageName] -- ^ Packages to omit from the "-package" / "-package-id" flags
-> Path Abs File
-> PackageDescription
-> Map NamedComponent (Set DotCabalPath)
-> m (Map NamedComponent BuildInfoOpts)
generatePkgDescOpts sourceMap installedMap omitPkgs cabalfp pkg componentPaths = do
distDir <- distDirFromDir cabalDir
let cabalmacros = autogenDir distDir </> $(mkRelFile "cabal_macros.h")
exists <- fileExists cabalmacros
let mcabalmacros =
if exists
then Just cabalmacros
else Nothing
let generate namedComponent binfo =
( namedComponent
, generateBuildInfoOpts
sourceMap
installedMap
mcabalmacros
cabalDir
distDir
omitPkgs
binfo
(fromMaybe mempty (M.lookup namedComponent componentPaths))
namedComponent)
return
( M.fromList
(concat
[ maybe
[]
(return . generate CLib . libBuildInfo)
(library pkg)
, fmap
(\exe ->
generate
(CExe (T.pack (exeName exe)))
(buildInfo exe))
(executables pkg)
, fmap
(\bench ->
generate
(CBench (T.pack (benchmarkName bench)))
(benchmarkBuildInfo bench))
(benchmarks pkg)
, fmap
(\test ->
generate
(CTest (T.pack (testName test)))
(testBuildInfo test))
(testSuites pkg)]))
where
cabalDir = parent cabalfp
-- | Generate GHC options for the target.
generateBuildInfoOpts
:: SourceMap
-> InstalledMap
-> Maybe (Path Abs File)
-> Path Abs Dir
-> Path Abs Dir
-> [PackageName]
-> BuildInfo
-> Set DotCabalPath
-> NamedComponent
-> BuildInfoOpts
generateBuildInfoOpts sourceMap installedMap mcabalmacros cabalDir distDir omitPkgs b dotCabalPaths componentName =
BuildInfoOpts
{ bioGhcOpts = ghcOpts b
-- NOTE for future changes: Due to this use of nubOrd (and other uses
-- downstream), these generated options must not rely on multiple
-- argument sequences. For example, ["--main-is", "Foo.hs", "--main-
-- is", "Bar.hs"] would potentially break due to the duplicate
-- "--main-is" being removed.
--
-- See https://github.com/commercialhaskell/stack/issues/1255
, bioGeneratedOpts = nubOrd $ concat
[extOpts b, srcOpts, includeOpts, macros, deps, extra b, extraDirs, fworks b, cObjectFiles]
, bioBuildable = buildable b
}
where
cObjectFiles =
mapMaybe (fmap toFilePath .
makeObjectFilePathFromC cabalDir componentName distDir)
cfiles
cfiles = mapMaybe dotCabalCFilePath (S.toList dotCabalPaths)
deps =
concat
[ case M.lookup (fromCabalPackageName name) installedMap of
Just (_, Stack.Types.Library _ident ipid) -> ["-package-id=" <> ghcPkgIdString ipid]
_ -> ["-package=" <> display name <>
maybe "" -- This empty case applies to e.g. base.
((("-" <>) . versionString) . sourceVersion)
(M.lookup (fromCabalPackageName name) sourceMap)]
| Dependency name _ <- targetBuildDepends b
, name `notElem` fmap toCabalPackageName omitPkgs]
-- Generates: -package=base -package=base16-bytestring-0.1.1.6 ...
sourceVersion (PSUpstream ver _ _) = ver
sourceVersion (PSLocal localPkg) = packageVersion (lpPackage localPkg)
macros =
case mcabalmacros of
Nothing -> []
Just cabalmacros ->
["-optP-include", "-optP" <> toFilePath cabalmacros]
ghcOpts = concatMap snd . filter (isGhc . fst) . options
where
isGhc GHC = True
isGhc _ = False
extOpts = map (("-X" ++) . display) . usedExtensions
srcOpts =
map
(("-i" <>) . FilePath.dropTrailingPathSeparator . toFilePath)
([cabalDir | null (hsSourceDirs b)] <>
mapMaybe toIncludeDir (hsSourceDirs b) <>
[autogenDir distDir,buildDir distDir]) ++
["-stubdir=" ++ FilePath.dropTrailingPathSeparator (toFilePath $ buildDir distDir)]
toIncludeDir "." = Just cabalDir
toIncludeDir x = fmap (cabalDir </>) (parseRelDir x)
includeOpts =
[ "-I" <> toFilePath absDir
| dir <- includeDirs b
, absDir <- case (parseAbsDir dir, parseRelDir dir) of
(Just ab, _ ) -> [ab]
(_ , Just rel) -> [cabalDir </> rel]
(Nothing, Nothing ) -> []
]
extra
= map ("-l" <>)
. extraLibs
extraDirs =
[ "-L" <> toFilePath absDir
| dir <- extraLibDirs b
, absDir <- case (parseAbsDir dir, parseRelDir dir) of
(Just ab, _ ) -> [ab]
(_ , Just rel) -> [cabalDir </> rel]
(Nothing, Nothing ) -> []
]
fworks = map (\fwk -> "-framework=" <> fwk) . frameworks
-- | Make the .o path from the .c file path for a component. Example:
--
-- @
-- executable FOO
-- c-sources: cbits/text_search.c
-- @
--
-- Produces
--
-- <dist-dir>/build/FOO/FOO-tmp/cbits/text_search.o
--
-- Example:
--
-- λ> makeObjectFilePathFromC
-- $(mkAbsDir "/Users/chris/Repos/hoogle")
-- CLib
-- $(mkAbsDir "/Users/chris/Repos/hoogle/.stack-work/Cabal-x.x.x/dist")
-- $(mkAbsFile "/Users/chris/Repos/hoogle/cbits/text_search.c")
-- Just "/Users/chris/Repos/hoogle/.stack-work/Cabal-x.x.x/dist/build/cbits/text_search.o"
-- λ> makeObjectFilePathFromC
-- $(mkAbsDir "/Users/chris/Repos/hoogle")
-- (CExe "hoogle")
-- $(mkAbsDir "/Users/chris/Repos/hoogle/.stack-work/Cabal-x.x.x/dist")
-- $(mkAbsFile "/Users/chris/Repos/hoogle/cbits/text_search.c")
-- Just "/Users/chris/Repos/hoogle/.stack-work/Cabal-x.x.x/dist/build/hoogle/hoogle-tmp/cbits/text_search.o"
-- λ>
makeObjectFilePathFromC
:: MonadThrow m
=> Path Abs Dir -- ^ The cabal directory.
-> NamedComponent -- ^ The name of the component.
-> Path Abs Dir -- ^ Dist directory.
-> Path Abs File -- ^ The path to the .c file.
-> m (Path Abs File) -- ^ The path to the .o file for the component.
makeObjectFilePathFromC cabalDir namedComponent distDir cFilePath = do
relCFilePath <- stripDir cabalDir cFilePath
relOFilePath <-
parseRelFile (replaceExtension (toFilePath relCFilePath) "o")
addComponentPrefix <- fromComponentName
return (addComponentPrefix (buildDir distDir) </> relOFilePath)
where
fromComponentName =
case namedComponent of
CLib -> return id
CExe name -> makeTmp name
CTest name -> makeTmp name
CBench name -> makeTmp name
makeTmp name = do
prefix <- parseRelDir (T.unpack name <> "/" <> T.unpack name <> "-tmp")
return (</> prefix)
-- | Make the autogen dir.
autogenDir :: Path Abs Dir -> Path Abs Dir
autogenDir distDir = buildDir distDir </> $(mkRelDir "autogen")
-- | Make the build dir.
buildDir :: Path Abs Dir -> Path Abs Dir
buildDir distDir = distDir </> $(mkRelDir "build")
-- | Make the component-specific subdirectory of the build directory.
getBuildComponentDir :: Maybe String -> Maybe (Path Rel Dir)
getBuildComponentDir Nothing = Nothing
getBuildComponentDir (Just name) = parseRelDir (name FilePath.</> (name ++ "-tmp"))
-- | Get all dependencies of the package (buildable targets only).
packageDependencies :: PackageDescription -> Map PackageName VersionRange
packageDependencies =
M.fromListWith intersectVersionRanges .
concatMap (fmap (depName &&& depRange) .
targetBuildDepends) .
allBuildInfo'
-- | Get all build tool dependencies of the package (buildable targets only).
packageToolDependencies :: PackageDescription -> Map BS.ByteString VersionRange
packageToolDependencies =
M.fromList .
concatMap (fmap (packageNameByteString . depName &&& depRange) .
buildTools) .
allBuildInfo'
-- | Get all dependencies of the package (buildable targets only).
packageDescTools :: PackageDescription -> [Dependency]
packageDescTools = concatMap buildTools . allBuildInfo'
-- | This is a copy-paste from Cabal's @allBuildInfo@ function, but with the
-- @buildable@ test removed. The reason is that (surprise) Cabal is broken,
-- see: https://github.com/haskell/cabal/issues/1725
allBuildInfo' :: PackageDescription -> [BuildInfo]
allBuildInfo' pkg_descr = [ bi | Just lib <- [library pkg_descr]
, let bi = libBuildInfo lib
, True || buildable bi ]
++ [ bi | exe <- executables pkg_descr
, let bi = buildInfo exe
, True || buildable bi ]
++ [ bi | tst <- testSuites pkg_descr
, let bi = testBuildInfo tst
, True || buildable bi
, testEnabled tst ]
++ [ bi | tst <- benchmarks pkg_descr
, let bi = benchmarkBuildInfo tst
, True || buildable bi
, benchmarkEnabled tst ]
-- | Get all files referenced by the package.
packageDescModulesAndFiles
:: (MonadLogger m, MonadIO m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m, MonadCatch m)
=> PackageDescription
-> m (Map NamedComponent (Set ModuleName), Map NamedComponent (Set DotCabalPath), Set (Path Abs File), [PackageWarning])
packageDescModulesAndFiles pkg = do
(libraryMods,libDotCabalFiles,libWarnings) <-
maybe
(return (M.empty, M.empty, []))
(asModuleAndFileMap libComponent libraryFiles)
(library pkg)
(executableMods,exeDotCabalFiles,exeWarnings) <-
liftM
foldTuples
(mapM
(asModuleAndFileMap exeComponent executableFiles)
(executables pkg))
(testMods,testDotCabalFiles,testWarnings) <-
liftM
foldTuples
(mapM (asModuleAndFileMap testComponent testFiles) (testSuites pkg))
(benchModules,benchDotCabalPaths,benchWarnings) <-
liftM
foldTuples
(mapM
(asModuleAndFileMap benchComponent benchmarkFiles)
(benchmarks pkg))
(dfiles) <- resolveGlobFiles (map (dataDir pkg FilePath.</>) (dataFiles pkg))
let modules = libraryMods <> executableMods <> testMods <> benchModules
files =
libDotCabalFiles <> exeDotCabalFiles <> testDotCabalFiles <>
benchDotCabalPaths
warnings = libWarnings <> exeWarnings <> testWarnings <> benchWarnings
return (modules, files, dfiles, warnings)
where
libComponent = const CLib
exeComponent = CExe . T.pack . exeName
testComponent = CTest . T.pack . testName
benchComponent = CBench . T.pack . benchmarkName
asModuleAndFileMap label f lib = do
(a,b,c) <- f lib
return (M.singleton (label lib) a, M.singleton (label lib) b, c)
foldTuples = foldl' (<>) (M.empty, M.empty, [])
-- | Resolve globbing of files (e.g. data files) to absolute paths.
resolveGlobFiles :: (MonadLogger m,MonadIO m,MonadThrow m,MonadReader (Path Abs File, Path Abs Dir) m,MonadCatch m)
=> [String] -> m (Set (Path Abs File))
resolveGlobFiles =
liftM (S.fromList . catMaybes . concat) .
mapM resolve
where
resolve name =
if '*' `elem` name
then explode name
else liftM return (resolveFileOrWarn name)
explode name = do
dir <- asks (parent . fst)
names <-
matchDirFileGlob'
(FL.toFilePath dir)
name
mapM resolveFileOrWarn names
matchDirFileGlob' dir glob =
catch
(liftIO (matchDirFileGlob_ dir glob))
(\(e :: IOException) ->
if isUserError e
then do
$logWarn
("Wildcard does not match any files: " <> T.pack glob <> "\n" <>
"in directory: " <> T.pack dir)
return []
else throwM e)
-- | This is a copy/paste of the Cabal library function, but with
--
-- @ext == ext'@
--
-- Changed to
--
-- @isSuffixOf ext ext'@
--
-- So that this will work:
--
-- @
-- λ> matchDirFileGlob_ "." "test/package-dump/*.txt"
-- ["test/package-dump/ghc-7.8.txt","test/package-dump/ghc-7.10.txt"]
-- @
--
matchDirFileGlob_ :: String -> String -> IO [String]
matchDirFileGlob_ dir filepath = case parseFileGlob filepath of
Nothing -> die $ "invalid file glob '" ++ filepath
++ "'. Wildcards '*' are only allowed in place of the file"
++ " name, not in the directory name or file extension."
++ " If a wildcard is used it must be with an file extension."
Just (NoGlob filepath') -> return [filepath']
Just (FileGlob dir' ext) -> do
files <- getDirectoryContents (dir FilePath.</> dir')
case [ dir' FilePath.</> file
| file <- files
, let (name, ext') = splitExtensions file
, not (null name) && isSuffixOf ext ext' ] of
[] -> die $ "filepath wildcard '" ++ filepath
++ "' does not match any files."
matches -> return matches
-- | Get all files referenced by the benchmark.
benchmarkFiles
:: (MonadLogger m, MonadIO m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m)
=> Benchmark -> m (Set ModuleName, Set DotCabalPath, [PackageWarning])
benchmarkFiles bench = do
dirs <- mapMaybeM resolveDirOrWarn (hsSourceDirs build)
dir <- asks (parent . fst)
(modules,files,warnings) <-
resolveFilesAndDeps
(Just $ benchmarkName bench)
(dirs ++ [dir])
(bnames <> exposed)
haskellModuleExts
cfiles <- buildOtherSources build
return (modules, files <> cfiles, warnings)
where
exposed =
case benchmarkInterface bench of
BenchmarkExeV10 _ fp -> [DotCabalMain fp]
BenchmarkUnsupported _ -> []
bnames = map DotCabalModule (otherModules build)
build = benchmarkBuildInfo bench
-- | Get all files referenced by the test.
testFiles
:: (MonadLogger m, MonadIO m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m)
=> TestSuite
-> m (Set ModuleName, Set DotCabalPath, [PackageWarning])
testFiles test = do
dirs <- mapMaybeM resolveDirOrWarn (hsSourceDirs build)
dir <- asks (parent . fst)
(modules,files,warnings) <-
resolveFilesAndDeps
(Just $ testName test)
(dirs ++ [dir])
(bnames <> exposed)
haskellModuleExts
cfiles <- buildOtherSources build
return (modules, files <> cfiles, warnings)
where
exposed =
case testInterface test of
TestSuiteExeV10 _ fp -> [DotCabalMain fp]
TestSuiteLibV09 _ mn -> [DotCabalModule mn]
TestSuiteUnsupported _ -> []
bnames = map DotCabalModule (otherModules build)
build = testBuildInfo test
-- | Get all files referenced by the executable.
executableFiles
:: (MonadLogger m, MonadIO m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m)
=> Executable
-> m (Set ModuleName, Set DotCabalPath, [PackageWarning])
executableFiles exe = do
dirs <- mapMaybeM resolveDirOrWarn (hsSourceDirs build)
dir <- asks (parent . fst)
(modules,files,warnings) <-
resolveFilesAndDeps
(Just $ exeName exe)
(dirs ++ [dir])
(map DotCabalModule (otherModules build) ++
[DotCabalMain (modulePath exe)])
haskellModuleExts
cfiles <- buildOtherSources build
return (modules, files <> cfiles, warnings)
where
build = buildInfo exe
-- | Get all files referenced by the library.
libraryFiles
:: (MonadLogger m, MonadIO m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m)
=> Library -> m (Set ModuleName, Set DotCabalPath, [PackageWarning])
libraryFiles lib = do
dirs <- mapMaybeM resolveDirOrWarn (hsSourceDirs build)
dir <- asks (parent . fst)
(modules,files,warnings) <-
resolveFilesAndDeps
Nothing
(dirs ++ [dir])
(names <> exposed)
haskellModuleExts
cfiles <- buildOtherSources build
return (modules, files <> cfiles, warnings)
where
names = bnames ++ exposed
exposed = map DotCabalModule (exposedModules lib)
bnames = map DotCabalModule (otherModules build)
build = libBuildInfo lib
-- | Get all C sources and extra source files in a build.
buildOtherSources :: (MonadLogger m,MonadIO m,MonadThrow m,MonadReader (Path Abs File, Path Abs Dir) m)
=> BuildInfo -> m (Set DotCabalPath)
buildOtherSources build =
do csources <- liftM
(S.map DotCabalCFilePath . S.fromList)
(mapMaybeM resolveFileOrWarn (cSources build))
jsources <- liftM
(S.map DotCabalFilePath . S.fromList)
(mapMaybeM resolveFileOrWarn (targetJsSources build))
return (csources <> jsources)
-- | Get the target's JS sources.
targetJsSources :: BuildInfo -> [FilePath]
#if MIN_VERSION_Cabal(1, 22, 0)
targetJsSources = jsSources
#else
targetJsSources = const []
#endif
-- | Get all dependencies of a package, including library,
-- executables, tests, benchmarks.
resolvePackageDescription :: PackageConfig
-> GenericPackageDescription
-> PackageDescription
resolvePackageDescription packageConfig (GenericPackageDescription desc defaultFlags mlib exes tests benches) =
desc {library =
fmap (resolveConditions rc updateLibDeps) mlib
,executables =
map (\(n, v) -> (resolveConditions rc updateExeDeps v){exeName=n})
exes
,testSuites =
map (\(n,v) -> (resolveConditions rc updateTestDeps v){testName=n})
tests
,benchmarks =
map (\(n,v) -> (resolveConditions rc updateBenchmarkDeps v){benchmarkName=n})
benches}
where flags =
M.union (packageConfigFlags packageConfig)
(flagMap defaultFlags)
rc = mkResolveConditions
(packageConfigCompilerVersion packageConfig)
(packageConfigPlatform packageConfig)
flags
updateLibDeps lib deps =
lib {libBuildInfo =
(libBuildInfo lib) {targetBuildDepends = deps}}
updateExeDeps exe deps =
exe {buildInfo =
(buildInfo exe) {targetBuildDepends = deps}}
updateTestDeps test deps =
test {testBuildInfo =
(testBuildInfo test) {targetBuildDepends = deps}
,testEnabled = packageConfigEnableTests packageConfig}
updateBenchmarkDeps benchmark deps =
benchmark {benchmarkBuildInfo =
(benchmarkBuildInfo benchmark) {targetBuildDepends = deps}
,benchmarkEnabled = packageConfigEnableBenchmarks packageConfig}
-- | Make a map from a list of flag specifications.
--
-- What is @flagManual@ for?
flagMap :: [Flag] -> Map FlagName Bool
flagMap = M.fromList . map pair
where pair :: Flag -> (FlagName, Bool)
pair (MkFlag (fromCabalFlagName -> name) _desc def _manual) = (name,def)
data ResolveConditions = ResolveConditions
{ rcFlags :: Map FlagName Bool
, rcCompilerVersion :: CompilerVersion
, rcOS :: OS
, rcArch :: Arch
}
-- | Generic a @ResolveConditions@ using sensible defaults.
mkResolveConditions :: CompilerVersion -- ^ Compiler version
-> Platform -- ^ installation target platform
-> Map FlagName Bool -- ^ enabled flags
-> ResolveConditions
mkResolveConditions compilerVersion (Platform arch os) flags = ResolveConditions
{ rcFlags = flags
, rcCompilerVersion = compilerVersion
, rcOS = os
, rcArch = arch
}
-- | Resolve the condition tree for the library.
resolveConditions :: (Monoid target,Show target)
=> ResolveConditions
-> (target -> cs -> target)
-> CondTree ConfVar cs target
-> target
resolveConditions rc addDeps (CondNode lib deps cs) = basic <> children
where basic = addDeps lib deps
children = mconcat (map apply cs)
where apply (cond,node,mcs) =
if condSatisfied cond
then resolveConditions rc addDeps node
else maybe mempty (resolveConditions rc addDeps) mcs
condSatisfied c =
case c of
Var v -> varSatisifed v
Lit b -> b
CNot c' ->
not (condSatisfied c')
COr cx cy ->
condSatisfied cx || condSatisfied cy
CAnd cx cy ->
condSatisfied cx && condSatisfied cy
varSatisifed v =
case v of
OS os -> os == rcOS rc
Arch arch -> arch == rcArch rc
Flag flag ->
fromMaybe False $ M.lookup (fromCabalFlagName flag) (rcFlags rc)
-- NOTE: ^^^^^ This should never happen, as all flags
-- which are used must be declared. Defaulting to
-- False.
Impl flavor range ->
case (flavor, rcCompilerVersion rc) of
(GHC, GhcVersion vghc) -> vghc `withinRange` range
(GHC, GhcjsVersion _ vghc) -> vghc `withinRange` range
#if MIN_VERSION_Cabal(1, 22, 0)
(GHCJS, GhcjsVersion vghcjs _) ->
#else
(OtherCompiler "ghcjs", GhcjsVersion vghcjs _) ->
#endif
vghcjs `withinRange` range
_ -> False
-- | Get the name of a dependency.
depName :: Dependency -> PackageName
depName (Dependency n _) = fromCabalPackageName n
-- | Get the version range of a dependency.
depRange :: Dependency -> VersionRange
depRange (Dependency _ r) = r
-- | Try to resolve the list of base names in the given directory by
-- looking for unique instances of base names applied with the given
-- extensions, plus find any of their module and TemplateHaskell
-- dependencies.
resolveFilesAndDeps
:: (MonadIO m, MonadLogger m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m)
=> Maybe String -- ^ Package component name
-> [Path Abs Dir] -- ^ Directories to look in.
-> [DotCabalDescriptor] -- ^ Base names.
-> [Text] -- ^ Extentions.
-> m (Set ModuleName,Set DotCabalPath,[PackageWarning])
resolveFilesAndDeps component dirs names0 exts = do
(dotCabalPaths,foundModules) <- loop names0 S.empty
warnings <- warnUnlisted foundModules
return (foundModules, dotCabalPaths, warnings)
where
loop [] doneModules = return (S.empty, doneModules)
loop names doneModules0 = do
resolvedFiles <- resolveFiles dirs names exts
pairs <- mapM (getDependencies component) resolvedFiles
let doneModules' =
S.union
doneModules0
(S.fromList (mapMaybe dotCabalModule names))
moduleDeps = S.unions (map fst pairs)
thDepFiles = concatMap snd pairs
modulesRemaining = S.difference moduleDeps doneModules'
(resolvedFiles',doneModules'') <-
loop (map DotCabalModule (S.toList modulesRemaining)) doneModules'
return
( S.union
(S.fromList
(resolvedFiles <> map DotCabalFilePath thDepFiles))
resolvedFiles'
, doneModules'')
warnUnlisted foundModules = do
let unlistedModules =
foundModules `S.difference`
S.fromList (mapMaybe dotCabalModule names0)
cabalfp <- asks fst
return $
if S.null unlistedModules
then []
else [ UnlistedModulesWarning
cabalfp
component
(S.toList unlistedModules)]
-- | Get the dependencies of a Haskell module file.
getDependencies
:: (MonadReader (Path Abs File, Path Abs Dir) m, MonadIO m)
=> Maybe String -> DotCabalPath -> m (Set ModuleName, [Path Abs File])
getDependencies component dotCabalPath =
case dotCabalPath of
DotCabalModulePath resolvedFile -> readResolvedHi resolvedFile
DotCabalMainPath resolvedFile -> readResolvedHi resolvedFile
DotCabalFilePath{} -> return (S.empty, [])
DotCabalCFilePath{} -> return (S.empty, [])
where
readResolvedHi resolvedFile = do
dumpHIDir <- getDumpHIDir
dir <- asks (parent . fst)
case stripDir dir resolvedFile of
Nothing -> return (S.empty, [])
Just fileRel -> do
let dumpHIPath =
FilePath.replaceExtension
(toFilePath (dumpHIDir </> fileRel))
".dump-hi"
dumpHIExists <- liftIO $ doesFileExist dumpHIPath
if dumpHIExists
then parseDumpHI dumpHIPath
else return (S.empty, [])
getDumpHIDir = do
bld <- asks snd
return $ maybe bld (bld </>) (getBuildComponentDir component)
-- | Parse a .dump-hi file into a set of modules and files.
parseDumpHI
:: (MonadReader (Path Abs File, void) m, MonadIO m)
=> FilePath -> m (Set ModuleName, [Path Abs File])
parseDumpHI dumpHIPath = do
dir <- asks (parent . fst)
dumpHI <- liftIO $ fmap C8.lines (C8.readFile dumpHIPath)
let startModuleDeps =
dropWhile (not . ("module dependencies:" `C8.isPrefixOf`)) dumpHI
moduleDeps =
S.fromList $
mapMaybe (simpleParse . T.unpack . decodeUtf8) $
C8.words $
C8.concat $
C8.dropWhile (/= ' ') (headDef "" startModuleDeps) :
takeWhile (" " `C8.isPrefixOf`) (tailSafe startModuleDeps)
thDeps =
-- The dependent file path is surrounded by quotes but is not escaped.
-- It can be an absolute or relative path.
mapMaybe
(parseAbsOrRelFile dir <=<
(fmap T.unpack .
(T.stripSuffix "\"" <=< T.stripPrefix "\"") .
T.dropWhileEnd (== '\r') . decodeUtf8 . C8.dropWhile (/= '"'))) $
filter ("addDependentFile \"" `C8.isPrefixOf`) dumpHI
return (moduleDeps, thDeps)
where
parseAbsOrRelFile dir fp =
case parseRelFile fp of
Just rel -> Just (dir </> rel)
Nothing -> parseAbsFile fp
-- | Try to resolve the list of base names in the given directory by
-- looking for unique instances of base names applied with the given
-- extensions.
resolveFiles
:: (MonadIO m, MonadLogger m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m)
=> [Path Abs Dir] -- ^ Directories to look in.
-> [DotCabalDescriptor] -- ^ Base names.
-> [Text] -- ^ Extentions.
-> m [DotCabalPath]
resolveFiles dirs names exts =
forMaybeM names (findCandidate dirs exts)
-- | Find a candidate for the given module-or-filename from the list
-- of directories and given extensions.
findCandidate
:: (MonadIO m, MonadLogger m, MonadThrow m, MonadReader (Path Abs File, Path Abs Dir) m)
=> [Path Abs Dir]
-> [Text]
-> DotCabalDescriptor
-> m (Maybe DotCabalPath)
findCandidate dirs exts name = do
pkg <- asks fst >>= parsePackageNameFromFilePath
candidates <- liftIO makeNameCandidates
case candidates of
[candidate] -> return (Just (cons candidate))
[] -> do
case name of
DotCabalModule mn
| display mn /= paths_pkg pkg -> logPossibilities dirs mn
_ -> return ()
return Nothing
(candidate:rest) -> do
warnMultiple name candidate rest
return (Just (cons candidate))
where
cons =
case name of
DotCabalModule{} -> DotCabalModulePath
DotCabalMain{} -> DotCabalMainPath
DotCabalFile{} -> DotCabalFilePath
DotCabalCFile{} -> DotCabalCFilePath
paths_pkg pkg = "Paths_" ++ packageNameString pkg
makeNameCandidates =
liftM (nubOrd . rights . concat) (mapM makeDirCandidates dirs)
makeDirCandidates :: Path Abs Dir
-> IO [Either ResolveException (Path Abs File)]
makeDirCandidates dir =
case name of
DotCabalMain fp -> liftM return (try (resolveFile' dir fp))
DotCabalFile fp -> liftM return (try (resolveFile' dir fp))
DotCabalCFile fp -> liftM return (try (resolveFile' dir fp))
DotCabalModule mn ->
mapM
((\ ext ->
try (resolveFile' dir (Cabal.toFilePath mn ++ "." ++ ext)))
. T.unpack)
exts
resolveFile'
:: (MonadIO m, MonadThrow m)
=> Path Abs Dir -> FilePath.FilePath -> m (Path Abs File)
resolveFile' x y = do
p <- parseCollapsedAbsFile (toFilePath x FilePath.</> y)
exists <- fileExists p
if exists
then return p
else throwM $ ResolveFileFailed x y (toFilePath p)
-- | Warn the user that multiple candidates are available for an
-- entry, but that we picked one anyway and continued.
warnMultiple
:: MonadLogger m
=> DotCabalDescriptor -> Path b t -> [Path b t] -> m ()
warnMultiple name candidate rest =
$logWarn
("There were multiple candidates for the Cabal entry \"" <>
showName name <>
"\" (" <>
T.intercalate "," (map (T.pack . toFilePath) rest) <>
"), picking " <>
T.pack (toFilePath candidate))
where showName (DotCabalModule name') = T.pack (display name')
showName (DotCabalMain fp) = T.pack fp
showName (DotCabalFile fp) = T.pack fp