1
+ {-# LANGUAGE ScopedTypeVariables #-}
1
2
-----------------------------------------------------------------------------
2
3
-- |
3
4
-- Module : Distribution.Client.List
@@ -13,6 +14,9 @@ module Distribution.Client.List (
13
14
list , info
14
15
) where
15
16
17
+ import Prelude ()
18
+ import Distribution.Client.Compat.Prelude
19
+
16
20
import Distribution.Package
17
21
( PackageName , Package (.. ), packageName
18
22
, packageVersion , UnitId )
@@ -33,7 +37,7 @@ import Distribution.Simple.Compiler
33
37
import Distribution.Simple.Program (ProgramDb )
34
38
import Distribution.Simple.Utils
35
39
( equating , comparing , die' , notice )
36
- import Distribution.Simple.Setup (fromFlag )
40
+ import Distribution.Simple.Setup (fromFlag , fromFlagOrDefault )
37
41
import Distribution.Simple.PackageIndex (InstalledPackageIndex )
38
42
import qualified Distribution.Simple.PackageIndex as InstalledPackageIndex
39
43
import Distribution.Version
@@ -61,64 +65,73 @@ import Distribution.Client.IndexUtils as IndexUtils
61
65
import Distribution.Client.FetchUtils
62
66
( isFetched )
63
67
68
+ import Data.Bits ((.|.) )
64
69
import Data.List
65
- ( sortBy , groupBy , sort , nub , intersperse , maximumBy , partition )
70
+ ( maximumBy , partition )
71
+ import Data.List.NonEmpty (groupBy , nonEmpty )
72
+ import qualified Data.List as L
66
73
import Data.Maybe
67
- ( listToMaybe , fromJust , fromMaybe , isJust , maybeToList )
74
+ ( fromJust )
68
75
import qualified Data.Map as Map
69
76
import Data.Tree as Tree
70
77
import Control.Monad
71
- ( MonadPlus ( mplus ), join )
78
+ ( join )
72
79
import Control.Exception
73
80
( assert )
74
- import Text.PrettyPrint as Disp
81
+ import qualified Text.PrettyPrint as Disp
82
+ import Text.PrettyPrint
83
+ ( lineLength , ribbonsPerLine , Doc , renderStyle , char
84
+ , (<+>) , nest , ($+$) , text , vcat , style , parens , fsep )
75
85
import System.Directory
76
86
( doesDirectoryExist )
77
87
78
88
import Distribution.Utils.ShortText (ShortText )
79
89
import qualified Distribution.Utils.ShortText as ShortText
90
+ import qualified Text.Regex.Base as Regex
91
+ import qualified Text.Regex.Posix.String as Regex
80
92
81
93
82
94
-- | Return a list of packages matching given search strings.
83
95
getPkgList :: Verbosity
84
96
-> PackageDBStack
85
97
-> RepoContext
86
- -> Compiler
87
- -> ProgramDb
98
+ -> Maybe (Compiler , ProgramDb )
88
99
-> ListFlags
89
100
-> [String ]
90
101
-> IO [PackageDisplayInfo ]
91
- getPkgList verbosity packageDBs repoCtxt comp progdb listFlags pats = do
92
- installedPkgIndex <- getInstalledPackages verbosity comp packageDBs progdb
102
+ getPkgList verbosity packageDBs repoCtxt mcompprogdb listFlags pats = do
103
+ installedPkgIndex <- for mcompprogdb $ \ (comp, progdb) ->
104
+ getInstalledPackages verbosity comp packageDBs progdb
93
105
sourcePkgDb <- getSourcePackages verbosity repoCtxt
106
+
107
+ regexps <- for pats $ \ pat -> do
108
+ e <- Regex. compile compOption Regex. execBlank pat
109
+ case e of
110
+ Right r -> return r
111
+ Left err -> die' verbosity $ " Failed to compile regex " ++ pat ++ " : " ++ snd err
112
+
94
113
let sourcePkgIndex = packageIndex sourcePkgDb
95
114
prefs name = fromMaybe anyVersion
96
115
(Map. lookup name (packagePreferences sourcePkgDb))
97
116
117
+ pkgsInfoMatching ::
118
+ [(PackageName , [Installed. InstalledPackageInfo ], [UnresolvedSourcePackage ])]
119
+ pkgsInfoMatching =
120
+ let matchingInstalled = maybe [] (matchingPackages InstalledPackageIndex. searchWithPredicate regexps) installedPkgIndex
121
+ matchingSource = matchingPackages (\ idx n -> concatMap snd (PackageIndex. searchWithPredicate idx n)) regexps sourcePkgIndex
122
+ in mergePackages matchingInstalled matchingSource
123
+
98
124
pkgsInfo ::
99
125
[(PackageName , [Installed. InstalledPackageInfo ], [UnresolvedSourcePackage ])]
100
126
pkgsInfo
101
127
-- gather info for all packages
102
- | null pats = mergePackages
103
- ( InstalledPackageIndex. allPackages installedPkgIndex)
104
- ( PackageIndex. allPackages sourcePkgIndex)
128
+ | null regexps = mergePackages
129
+ ( maybe [] InstalledPackageIndex. allPackages installedPkgIndex)
130
+ ( PackageIndex. allPackages sourcePkgIndex)
105
131
106
132
-- gather info for packages matching search term
107
133
| otherwise = pkgsInfoMatching
108
134
109
- pkgsInfoMatching ::
110
- [(PackageName , [Installed. InstalledPackageInfo ], [UnresolvedSourcePackage ])]
111
- pkgsInfoMatching =
112
- let matchingInstalled = matchingPackages
113
- ipiSearch
114
- installedPkgIndex
115
- matchingSource = matchingPackages
116
- (\ idx n ->
117
- concatMap snd
118
- (piSearch idx n))
119
- sourcePkgIndex
120
- in mergePackages matchingInstalled matchingSource
121
-
122
135
matches :: [PackageDisplayInfo ]
123
136
matches = [ mergePackageInfo pref
124
137
installedPkgs sourcePkgs selectedPkg False
@@ -128,29 +141,28 @@ getPkgList verbosity packageDBs repoCtxt comp progdb listFlags pats = do
128
141
selectedPkg = latestWithPref pref sourcePkgs ]
129
142
return matches
130
143
where
131
- onlyInstalled = fromFlag (listInstalled listFlags)
132
- exactMatch = fromFlag (listExactMatch listFlags)
133
- ipiSearch | exactMatch = InstalledPackageIndex. searchByNameExact
134
- | otherwise = InstalledPackageIndex. searchByNameSubstring
135
- piSearch | exactMatch = PackageIndex. searchByNameExact
136
- | otherwise = PackageIndex. searchByNameSubstring
137
- matchingPackages search index =
144
+ onlyInstalled = fromFlagOrDefault False (listInstalled listFlags)
145
+ caseInsensitive = fromFlagOrDefault True (listCaseInsensitive listFlags)
146
+
147
+ compOption | caseInsensitive = Regex. compExtended .|. Regex. compIgnoreCase
148
+ | otherwise = Regex. compExtended
149
+
150
+ matchingPackages search regexps index =
138
151
[ pkg
139
- | pat <- pats
140
- , pkg <- search index pat ]
152
+ | re <- regexps
153
+ , pkg <- search index ( Regex. matchTest re) ]
141
154
142
155
143
156
-- | Show information about packages.
144
157
list :: Verbosity
145
158
-> PackageDBStack
146
159
-> RepoContext
147
- -> Compiler
148
- -> ProgramDb
160
+ -> Maybe (Compiler , ProgramDb )
149
161
-> ListFlags
150
162
-> [String ]
151
163
-> IO ()
152
- list verbosity packageDBs repos comp progdb listFlags pats = do
153
- matches <- getPkgList verbosity packageDBs repos comp progdb listFlags pats
164
+ list verbosity packageDBs repos mcompProgdb listFlags pats = do
165
+ matches <- getPkgList verbosity packageDBs repos mcompProgdb listFlags pats
154
166
155
167
if simpleOutput
156
168
then putStr $ unlines
@@ -204,7 +216,7 @@ info verbosity packageDBs repoCtxt comp progdb
204
216
(fromFlag $ globalWorldFile globalFlags)
205
217
sourcePkgs' userTargets
206
218
207
- pkgsinfo <- sequence
219
+ pkgsinfo <- sequenceA
208
220
[ do pkginfo <- either (die' verbosity) return $
209
221
gatherPkgInfo prefs
210
222
installedPkgIndex sourcePkgIndex
@@ -330,16 +342,16 @@ showPackageSummaryInfo pkginfo =
330
342
$+$ text " "
331
343
where
332
344
maybeShowST l s f
333
- | ShortText. null l = empty
345
+ | ShortText. null l = Disp. empty
334
346
| otherwise = text s <+> f (ShortText. fromShortText l)
335
347
336
348
showPackageDetailedInfo :: PackageDisplayInfo -> String
337
349
showPackageDetailedInfo pkginfo =
338
350
renderStyle (style {lineLength = 80 , ribbonsPerLine = 1 }) $
339
351
char ' *' <+> pretty (pkgName pkginfo)
340
- Disp. <> maybe empty (\ v -> char ' -' Disp. <> pretty v) (selectedVersion pkginfo)
352
+ <<>> maybe Disp. empty (\ v -> char ' -' Disp. <> pretty v) (selectedVersion pkginfo)
341
353
<+> text (replicate (16 - length (prettyShow (pkgName pkginfo))) ' ' )
342
- Disp. < > parens pkgkind
354
+ <<> > parens pkgkind
343
355
$+$
344
356
(nest 4 $ vcat [
345
357
entryST " Synopsis" synopsis hideIfNull reflowParagraphs
@@ -363,14 +375,14 @@ showPackageDetailedInfo pkginfo =
363
375
, entry " Dependencies" dependencies hideIfNull (commaSep dispExtDep)
364
376
, entry " Documentation" haddockHtml showIfInstalled text
365
377
, entry " Cached" haveTarball alwaysShow dispYesNo
366
- , if not (hasLib pkginfo) then empty else
378
+ , if not (hasLib pkginfo) then mempty else
367
379
text " Modules:" $+$ nest 4 (vcat (map pretty . sort . modules $ pkginfo))
368
380
])
369
381
$+$ text " "
370
382
where
371
383
entry fname field cond format = case cond (field pkginfo) of
372
384
Nothing -> label <+> format (field pkginfo)
373
- Just Nothing -> empty
385
+ Just Nothing -> mempty
374
386
Just (Just other) -> label <+> text other
375
387
where
376
388
label = text fname Disp. <> char ' :' Disp. <> padding
@@ -407,7 +419,7 @@ showPackageDetailedInfo pkginfo =
407
419
| hasLib pkginfo = text " library"
408
420
| hasExes = text " programs"
409
421
| hasExe pkginfo = text " program"
410
- | otherwise = empty
422
+ | otherwise = mempty
411
423
412
424
413
425
reflowParagraphs :: String -> Doc
@@ -416,7 +428,7 @@ reflowParagraphs =
416
428
. intersperse (text " " ) -- re-insert blank lines
417
429
. map (fsep . map text . concatMap words ) -- reflow paragraphs
418
430
. filter (/= [" " ])
419
- . groupBy (\ x y -> " " `notElem` [x,y]) -- break on blank lines
431
+ . L. groupBy (\ x y -> " " `notElem` [x,y]) -- break on blank lines
420
432
. lines
421
433
422
434
reflowLines :: String -> Doc
@@ -548,7 +560,7 @@ mergePackages installedPkgs sourcePkgs =
548
560
collect (OnlyInRight (name,as)) = (name, [] , as)
549
561
550
562
groupOn :: Ord key => (a -> key ) -> [a ] -> [(key ,[a ])]
551
- groupOn key = map (\ xs -> (key (head xs), xs))
563
+ groupOn key = map (\ xs -> (key (head xs), toList xs))
552
564
. groupBy (equating key)
553
565
. sortBy (comparing key)
554
566
@@ -586,9 +598,12 @@ interestingVersions pref =
586
598
. reorderTree (\ (Node (v,_) _) -> pref (mkVersion v))
587
599
. reverseTree
588
600
. mkTree
589
- . map versionNumbers
601
+ . map (or0 . versionNumbers)
590
602
591
603
where
604
+ or0 [] = 0 :| []
605
+ or0 (x: xs) = x :| xs
606
+
592
607
swizzleTree = unfoldTree (spine [] )
593
608
where
594
609
spine ts' (Node x [] ) = (x, ts')
@@ -601,12 +616,17 @@ interestingVersions pref =
601
616
602
617
reverseTree (Node x cs) = Node x (reverse (map reverseTree cs))
603
618
619
+ mkTree :: forall a . Eq a => [NonEmpty a ] -> Tree ([a ], Bool )
604
620
mkTree xs = unfoldTree step (False , [] , xs)
605
621
where
622
+ step :: (Bool , [a ], [NonEmpty a ]) -> (([a ], Bool ), [(Bool , [a ], [NonEmpty a ])])
606
623
step (node,ns,vs) =
607
624
( (reverse ns, node)
608
- , [ (any null vs', n: ns, filter (not . null ) vs')
609
- | (n, vs') <- groups vs ]
625
+ , [ (any null vs', n: ns, mapMaybe nonEmpty (toList vs'))
626
+ | (n, vs') <- groups vs
627
+ ]
610
628
)
611
- groups = map (\ g -> (head (head g), map tail g))
629
+
630
+ groups :: [NonEmpty a ] -> [(a , NonEmpty [a ])]
631
+ groups = map (\ g -> (head (head g), fmap tail g))
612
632
. groupBy (equating head )
0 commit comments