Skip to content

Commit 0c41d67

Browse files
authored
Merge pull request #6806 from phadej/regex-list
Regex list
2 parents d220810 + 6a01fb1 commit 0c41d67

File tree

8 files changed

+171
-133
lines changed

8 files changed

+171
-133
lines changed

Cabal/Distribution/Simple/PackageIndex.hs

Lines changed: 8 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ module Distribution.Simple.PackageIndex (
7777
searchByName,
7878
SearchResult(..),
7979
searchByNameSubstring,
80-
searchByNameExact,
80+
searchWithPredicate,
8181

8282
-- ** Bulk queries
8383
allPackages,
@@ -527,24 +527,19 @@ data SearchResult a = None | Unambiguous a | Ambiguous [a]
527527
-- That is, all packages that contain the given string in their name.
528528
--
529529
searchByNameSubstring :: PackageIndex a -> String -> [a]
530-
searchByNameSubstring =
531-
searchByNameInternal False
532-
533-
searchByNameExact :: PackageIndex a -> String -> [a]
534-
searchByNameExact =
535-
searchByNameInternal True
530+
searchByNameSubstring index searchterm =
531+
searchWithPredicate index (\n -> lsearchterm `isInfixOf` lowercase n)
532+
where lsearchterm = lowercase searchterm
536533

537-
searchByNameInternal :: Bool -> PackageIndex a -> String -> [a]
538-
searchByNameInternal exactMatch index searchterm =
534+
-- | @since 3.4.0.0
535+
searchWithPredicate :: PackageIndex a -> (String -> Bool) -> [a]
536+
searchWithPredicate index predicate =
539537
[ pkg
540538
-- Don't match internal packages
541539
| ((pname, LMainLibName), pvers) <- Map.toList (packageIdIndex index)
542-
, if exactMatch
543-
then searchterm == unPackageName pname
544-
else lsearchterm `isInfixOf` lowercase (unPackageName pname)
540+
, predicate (unPackageName pname)
545541
, pkgs <- Map.elems pvers
546542
, pkg <- pkgs ]
547-
where lsearchterm = lowercase searchterm
548543

549544
--
550545
-- * Special queries

cabal-install/Distribution/Client/List.hs

Lines changed: 71 additions & 51 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
12
-----------------------------------------------------------------------------
23
-- |
34
-- Module : Distribution.Client.List
@@ -13,6 +14,9 @@ module Distribution.Client.List (
1314
list, info
1415
) where
1516

17+
import Prelude ()
18+
import Distribution.Client.Compat.Prelude
19+
1620
import Distribution.Package
1721
( PackageName, Package(..), packageName
1822
, packageVersion, UnitId )
@@ -33,7 +37,7 @@ import Distribution.Simple.Compiler
3337
import Distribution.Simple.Program (ProgramDb)
3438
import Distribution.Simple.Utils
3539
( equating, comparing, die', notice )
36-
import Distribution.Simple.Setup (fromFlag)
40+
import Distribution.Simple.Setup (fromFlag, fromFlagOrDefault)
3741
import Distribution.Simple.PackageIndex (InstalledPackageIndex)
3842
import qualified Distribution.Simple.PackageIndex as InstalledPackageIndex
3943
import Distribution.Version
@@ -61,64 +65,73 @@ import Distribution.Client.IndexUtils as IndexUtils
6165
import Distribution.Client.FetchUtils
6266
( isFetched )
6367

68+
import Data.Bits ((.|.))
6469
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
6673
import Data.Maybe
67-
( listToMaybe, fromJust, fromMaybe, isJust, maybeToList )
74+
( fromJust )
6875
import qualified Data.Map as Map
6976
import Data.Tree as Tree
7077
import Control.Monad
71-
( MonadPlus(mplus), join )
78+
( join )
7279
import Control.Exception
7380
( 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)
7585
import System.Directory
7686
( doesDirectoryExist )
7787

7888
import Distribution.Utils.ShortText (ShortText)
7989
import qualified Distribution.Utils.ShortText as ShortText
90+
import qualified Text.Regex.Base as Regex
91+
import qualified Text.Regex.Posix.String as Regex
8092

8193

8294
-- | Return a list of packages matching given search strings.
8395
getPkgList :: Verbosity
8496
-> PackageDBStack
8597
-> RepoContext
86-
-> Compiler
87-
-> ProgramDb
98+
-> Maybe (Compiler, ProgramDb)
8899
-> ListFlags
89100
-> [String]
90101
-> 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
93105
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+
94113
let sourcePkgIndex = packageIndex sourcePkgDb
95114
prefs name = fromMaybe anyVersion
96115
(Map.lookup name (packagePreferences sourcePkgDb))
97116

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+
98124
pkgsInfo ::
99125
[(PackageName, [Installed.InstalledPackageInfo], [UnresolvedSourcePackage])]
100126
pkgsInfo
101127
-- 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)
105131

106132
-- gather info for packages matching search term
107133
| otherwise = pkgsInfoMatching
108134

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-
122135
matches :: [PackageDisplayInfo]
123136
matches = [ mergePackageInfo pref
124137
installedPkgs sourcePkgs selectedPkg False
@@ -128,29 +141,28 @@ getPkgList verbosity packageDBs repoCtxt comp progdb listFlags pats = do
128141
selectedPkg = latestWithPref pref sourcePkgs ]
129142
return matches
130143
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 =
138151
[ pkg
139-
| pat <- pats
140-
, pkg <- search index pat ]
152+
| re <- regexps
153+
, pkg <- search index (Regex.matchTest re) ]
141154

142155

143156
-- | Show information about packages.
144157
list :: Verbosity
145158
-> PackageDBStack
146159
-> RepoContext
147-
-> Compiler
148-
-> ProgramDb
160+
-> Maybe (Compiler, ProgramDb)
149161
-> ListFlags
150162
-> [String]
151163
-> 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
154166

155167
if simpleOutput
156168
then putStr $ unlines
@@ -204,7 +216,7 @@ info verbosity packageDBs repoCtxt comp progdb
204216
(fromFlag $ globalWorldFile globalFlags)
205217
sourcePkgs' userTargets
206218

207-
pkgsinfo <- sequence
219+
pkgsinfo <- sequenceA
208220
[ do pkginfo <- either (die' verbosity) return $
209221
gatherPkgInfo prefs
210222
installedPkgIndex sourcePkgIndex
@@ -330,16 +342,16 @@ showPackageSummaryInfo pkginfo =
330342
$+$ text ""
331343
where
332344
maybeShowST l s f
333-
| ShortText.null l = empty
345+
| ShortText.null l = Disp.empty
334346
| otherwise = text s <+> f (ShortText.fromShortText l)
335347

336348
showPackageDetailedInfo :: PackageDisplayInfo -> String
337349
showPackageDetailedInfo pkginfo =
338350
renderStyle (style {lineLength = 80, ribbonsPerLine = 1}) $
339351
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)
341353
<+> text (replicate (16 - length (prettyShow (pkgName pkginfo))) ' ')
342-
Disp.<> parens pkgkind
354+
<<>> parens pkgkind
343355
$+$
344356
(nest 4 $ vcat [
345357
entryST "Synopsis" synopsis hideIfNull reflowParagraphs
@@ -363,14 +375,14 @@ showPackageDetailedInfo pkginfo =
363375
, entry "Dependencies" dependencies hideIfNull (commaSep dispExtDep)
364376
, entry "Documentation" haddockHtml showIfInstalled text
365377
, entry "Cached" haveTarball alwaysShow dispYesNo
366-
, if not (hasLib pkginfo) then empty else
378+
, if not (hasLib pkginfo) then mempty else
367379
text "Modules:" $+$ nest 4 (vcat (map pretty . sort . modules $ pkginfo))
368380
])
369381
$+$ text ""
370382
where
371383
entry fname field cond format = case cond (field pkginfo) of
372384
Nothing -> label <+> format (field pkginfo)
373-
Just Nothing -> empty
385+
Just Nothing -> mempty
374386
Just (Just other) -> label <+> text other
375387
where
376388
label = text fname Disp.<> char ':' Disp.<> padding
@@ -407,7 +419,7 @@ showPackageDetailedInfo pkginfo =
407419
| hasLib pkginfo = text "library"
408420
| hasExes = text "programs"
409421
| hasExe pkginfo = text "program"
410-
| otherwise = empty
422+
| otherwise = mempty
411423

412424

413425
reflowParagraphs :: String -> Doc
@@ -416,7 +428,7 @@ reflowParagraphs =
416428
. intersperse (text "") -- re-insert blank lines
417429
. map (fsep . map text . concatMap words) -- reflow paragraphs
418430
. filter (/= [""])
419-
. groupBy (\x y -> "" `notElem` [x,y]) -- break on blank lines
431+
. L.groupBy (\x y -> "" `notElem` [x,y]) -- break on blank lines
420432
. lines
421433

422434
reflowLines :: String -> Doc
@@ -548,7 +560,7 @@ mergePackages installedPkgs sourcePkgs =
548560
collect (OnlyInRight (name,as)) = (name, [], as)
549561

550562
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))
552564
. groupBy (equating key)
553565
. sortBy (comparing key)
554566

@@ -586,9 +598,12 @@ interestingVersions pref =
586598
. reorderTree (\(Node (v,_) _) -> pref (mkVersion v))
587599
. reverseTree
588600
. mkTree
589-
. map versionNumbers
601+
. map (or0 . versionNumbers)
590602

591603
where
604+
or0 [] = 0 :| []
605+
or0 (x:xs) = x :| xs
606+
592607
swizzleTree = unfoldTree (spine [])
593608
where
594609
spine ts' (Node x []) = (x, ts')
@@ -601,12 +616,17 @@ interestingVersions pref =
601616

602617
reverseTree (Node x cs) = Node x (reverse (map reverseTree cs))
603618

619+
mkTree :: forall a. Eq a => [NonEmpty a] -> Tree ([a], Bool)
604620
mkTree xs = unfoldTree step (False, [], xs)
605621
where
622+
step :: (Bool, [a], [NonEmpty a]) -> (([a], Bool), [(Bool, [a], [NonEmpty a])])
606623
step (node,ns,vs) =
607624
( (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+
]
610628
)
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))
612632
. groupBy (equating head)

0 commit comments

Comments
 (0)